
Henning Thielemann
On Fri, 2 Jan 2009, Achim Schneider wrote:
Henning Thielemann
wrote: If it is generally possible to use unsafeInterleaveIO such that it executes actions in the right order, wouldn't this allow the definition of a general lazy IO monad?
The question is what "right order" means.
Let B1..Bn be some arbitrary IO-Actions. Let A1..An be some arbitrary IO Actions passed to unsafeInterleaveIO
You're guaranteed that a) Bk+1 is executed after Bk b) Ak+1 is executed after Ak
, all by virtue of the IO Monad.
If all Ak's are defered using individual unsafeInterleaveIO's then it is not guaranteed that A[k+1] is executed after A[k]. That's my problem.
Check: Prelude> fmap snd $ Monad.liftM2 (,) (unsafeInterleaveIO getLine) Prelude> (unsafeInterleaveIO getLine)
If unsafely interleaved actions would be executed in order, then this would first ask you for the first pair member, then for the second one, then echo the second one. Actually it asks only for the second one and prints it.
module Main where import System.IO.Unsafe chooseAct :: String -> IO (IO ()) chooseAct s = do putStrLn $ s ++ "?" l <- getLine if (l == s) then return $ putStrLn $ "w00t! a " ++ s else return $ putStrLn "bah" getActs :: IO [IO ()] getActs = mapM chooseAct ["foo", "bar", "baz"] main0 = unsafeInterleaveIO getActs >>= unsafeInterleaveIO . sequence_ main1 = unsafeInterleaveIO getActs >>= sequence_ main = main0 >> main1 There you've got the ordering. It's quite easy to write a haskell program that reduces itself to main = return (), though. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.