
Jump to question 1 and question 2 most simple streaming example: ============= ======================================================= module Main where import System.IO import Control.Monad main = do lines <- liftM lines getContents mapM_ print lines -- * =========== ======================================================= Matthiew:
The sequencing imposed by the IO monad means that the first mapM must complete before the second can start. This does not apply to the example above, does it? This example behaves like a pipe output is written before all input has been read. But we have 2 IO actions, don't we?: lines <- liftM lines getContents and mapM_ print lines
question 1: So this example should "hang", as well, shouldn't it? Bulat: Its getting interesting: This works as expected. ============= ======================================================= module Main where import Data.Time.Clock import Data.Time import Control.Monad import System.Exit import System.IO import System.IO.Unsafe handleChar :: Show a => (Char, a) -> IO () handleChar ('s', _) = exitWith (ExitFailure 1) handleChar tuple = print tuple addTimeCode a = liftM ( (,) a) getCurrentTime main = do hSetBuffering stdin NoBuffering liftM (take 4) (hGetContents stdin) >>= unsafeInterleavedMapM addTimeCode >>= mapM print unsafeInterleavedMapM f (x:xs) = do a <- f x as <- unsafeInterleaveIO (unsafeInterleavedMapM f xs) return (a:as) ============= ======================================================= When also using unsafeInterleavedMapM for the second mapM the program will stop after processing the first list item. question 2 I can't see why this is the case. Continuation does work as well: ============= continuation example =================================== module Main where import Control.Monad.Cont import System.Exit import System.IO import Data.Time takeChar [] = exitWith ExitSuccess takeChar (c:cs) = do print c print =<< getCurrentTime when (c =='s') $ exitWith $ ExitFailure 1 takeChar cs main = do hSetBuffering stdin NoBuffering getContents >>= takeChar ============= ======================================================= Marc