[Haskell-cafe] Exception: Too many open files

Bas van Dijk basvandijk at home.nl
Mon Oct 23 17:03:55 EDT 2006


On Monday 23 October 2006 21:50, Tomasz Zielonka wrote:
> unsafeInterleaveMapIO f (x:xs) = unsafeInterleaveIO $ do
>         y <- f x
>         ys <- unsafeInterleaveMapIO f xs
>         return (y : ys)
>     unsafeInterleaveMapIO _ [] = return []

Great it works! I didn't know about unsafeInterleaveIO [1]. 

Why is it called 'unsafe'?

And how does the laziness work? Is it because of the 'let r = ... in (s, r)'? 

[1] ghc/libraries/base/GHC/IOBase.lhs:249:
-------------------------------------------------------------------------------
{-|
'unsafeInterleaveIO' allows 'IO' computation to be deferred lazily.
When passed a value of type @IO a@, the 'IO' will only be performed
when the value of the @a@ is demanded.  This is used to implement lazy
file reading, see 'System.IO.hGetContents'.
-}
{-# INLINE unsafeInterleaveIO #-}
unsafeInterleaveIO :: IO a -> IO a
unsafeInterleaveIO (IO m)
  = IO ( \ s -> let
                   r = case m s of (# _, res #) -> res
                in
                (# s, r #))

-- We believe that INLINE on unsafeInterleaveIO is safe, because the
-- state from this IO thread is passed explicitly to the interleaved
-- IO, so it cannot be floated out and shared.
-------------------------------------------------------------------------------

Thanks,

Bas van Dijk


More information about the Haskell-Cafe mailing list