[Haskell-cafe] Lazy IO
Reid Barton
rwbarton at math.harvard.edu
Thu Jul 10 09:47:15 EDT 2008
On Wed, Jul 09, 2008 at 11:05:47PM -0400, Ronald Guida wrote:
> Question: If I can't change my function f (in this case, accumulator),
> then is it possible to get the effect I want without having to resort
> to "unsafeInterleaveIO"?
Here's a possibility; you may or may not like it.
module Main
where
import Control.Concurrent
import Control.Concurrent.Chan
import Control.Concurrent.MVar
import Control.Monad
{- promptInt, accumulator, makeAccPrompt as before -}
main :: IO ()
main = do
inChan <- newChan
outMVar <- newEmptyMVar
forkIO $ (getChanContents inChan) >>= (mapM_ (putMVar outMVar) . accumulator)
let go = do
p <- takeMVar outMVar
m <- promptInt (makeAccPrompt p)
case m of
Just n -> do
writeChan inChan n
ns <- go
return $ n:ns
Nothing -> return []
xs <- go
print xs
The unsafeInterleaveIO is now hidden inside getChanContents. (I have
an outMVar rather than an outChan just in case accumulator could
produce lots of output before consuming much of its input.)
Regards,
Reid Barton
More information about the Haskell-Cafe
mailing list