2008/12/31 Paolino <paolo.verone...@gmail.com>: > I must ask why runWriterT k :: State s (a,[Int]) is working. > Looks like I could runIO the same way I evalState there. > In that case I wouldn't wait for the State s action to finish. > > Thanks
Assuming you have Control.Monad.State.Lazy (which I think is the default), here is the difference: (>>=) for State: ma >>= f = State $ \s0 -> let (a, s1) = runState ma s0 in runState (f a) s1 The "let" is a lazy pattern match; in particular, consider this code: runState (do put 0 put 1) 2 -> desugar runState (put 0 >> put 1) 2 The rest is lazy evaluation in action! -> apply >> runState (put 0 >>= \_ -> put 1) 2 -> apply >>= runState (State $ \s0 -> let (a, s1) = runState (put 0) s0 in runState (put 1) s1 ) 2 -> apply runState (\s0 -> let (a,s1) = runState (put 0) s0 in runState (put 1) s1 ) 2 -> beta reduce let s0 = 2 in let (a,s1) = runState (put 0) s0 in runState (put 1) s1 -> apply put let s0 = 2 in let (a,s1) = runState (put 0) s0 in runState (State $ \_ -> ((), 1)) s1 -> apply runState let s0 = 2 in let (a,s1) = runState (put 0) s0 in (\_ -> ((), 1)) s1 -> beta reduce let s0 = 2 in let (a,s1) = runState (put 0) s0 in ((), 1) -> garbage collect ((), 1) Note that at no point were s0, a, or s1 evaluated; so there was no need to evaluate the state at all! Furthermore, even if you replace (put 0) with a computation that loops and looks at the state at each point, the result is immediately a pair, so future computation can continue. Now lets contrast with IO: (>>=) for IO (taking out the "unboxed pairs" stuff which muddles the issue) ma >>= f = IO $ \s0 -> case (unIO ma s0) of (a, s1) -> unIO (f a) s1 (Note that this is the basically the same as Control.Monad.State.Strict) Consider main = do putStrLn "hello" putStrLn "world" We'll use this definition of putStrLn for simplicity's sake: > -- primitive, unsafe, side-effecting function. > putStrLn# :: String -> () > > putStrLn :: String -> IO () > putStrLn s = IO $ \w -> seq (putStrLn# s) ((), w) So putStrLn is an IO action which takes a "world" (a dummy value that doesn't really exist) as input, and before it gives any output, forces the evaluation of a side-effecting primitive function via seq. It then returns a pair containing the result (), and the original "world" argument as the state. Desugar: main = (putStrLn "hello" >> putStrLn "world") Send to the runtime: unIO (putStrLn "hello" >> putStrLn "world") world# Now lets evaluate it. -> Apply >> unIO (putStrLn "hello" >>= \_ -> putStrLn "world") world# -> Apply >>= unIO (IO $ \w0 -> case unIO (putStrLn "hello") w0 of (a, w1) -> unIO ((\_ -> putStrLn "world") a) w1 -> Apply unIO and beta-reduce case unIO (putStrLn "hello") world# of (a, w1) -> unIO ((\_ -> putStrLn "world") a) w1 Note that the evaluation order is different here; since we have a case statement, we must force the evaluation of the first putStrLn to make sure it evaluates to a pair! -> Apply putStrLn case unIO (IO $ \w -> seq (putStrLn# "hello") ((), w)) world# of (a, w1) -> unIO ((\_ -> putStrLn "world") a) w1 -> apply unIO & beta-reduce case seq (putStrLn# "hello") ((), world#) of (a, w1) -> unIO ((\_ -> putStrLn "world") a) w1 -> seq evaluates putStrLn#, side effect happens here! case ((), world#) of (a, w1) -> unIO ((\_ -> putStrLn "world") a) w1 -> pattern match in case succeeds now let a = () w1 = world# in unIO ((\_ -> putStrLn "world") a) w1 -> beta reduce & garbage collect unIO (putStrLn "world") world# -> apply putStrLn unIO (IO $ \w -> seq (putStrLn# "world") ((), w)) world# -> apply unIO & beta reduce seq (putStrLn# "world") ((), world#) -> seq evaluates putStrLn#, side effect happens here! ((), world#) Now, you are probably wondering for the reason behind the use of "case" vs. "let". It's pretty simple; lets evaluate that last code using the lazy method like State. Everything is the same up to "apply >>=", so start there: unIO (putStrLn "hello" >>= \_ -> putStrLn "world") world# -> Apply >>= unIO (IO $ \w0 -> let (a, w1) = unIO (putStrLn "hello") w0 in unIO (putStrLn "world") w1 ) world# -> apply unIO and beta-reduce let (a, w1) = unIO (putStrLn "hello") world# in unIO (putStrLn "world") w1 -> apply putStrLn (the second one!) let (a, w1) = unIO (putStrLn "hello") world# in unIO (IO $ \w -> seq (putStrLn# "world") ((), w)) w1 -> apply unIO and beta-reduce let (a, w1) = unIO (putStrLn "hello") world# in seq (putStrLn# "world" w1) ((), w1) Now we call putStrLn# which causes a side effect. It ignores the "world" argument and just returns it unchanged, of course. We could also add extra machinery to the compiler to force it to treat the "world" argument as strictly, but you can see that using "lazy" really changes the order of evaluation, which ends up making the code much harder to optimize. -> seq evaluates putStrLn# (printing "world", oops!) let (a,w1) = unIO (putStrLn "hello" world#) in ((), w1) We need w1 here, so we have to force evaluation of the pair to extract it. -> apply putStrLn let (a,w1) = unIO (IO $ \w -> seq (putStrLn# "hello") ((), w)) world# in ((), w1) -> apply unIO & beta-reduce let (a,w1) = seq (putStrLn# "hello") ((), world#) in ((), w1) -> seq evaluates putStrLn#, printing "hello" let (a,w1) = ((), world#) in ((), w1) -> garbage-collect ((), world#) I've omitted some of the details, and this isn't exactly how it works. In particular, I believe GHC's primitive operations take the World# argument directly, so you can argue that this behavior wouldn't happen as long as that argument was considered "strict". But the "lazy" behavior makes the order of evaluation much harder to predict, which I think is considered to be bad for IO, which lives on the "imperative" side of the imperative/functional divide. In particular, unsafeInterleaveIO (and its friend getContents) would be even more difficult to use correctly if IO used a "lazy state" monad. It might be possible to build a "lazy-ify" monad transformer which would make this work. In particular, I think Oleg's LogicT transformer[1] does something of the sort, only applying side effects where they are required in order to get "the next result" in a nondeterministic computation. -- ryan [1] http://okmij.org/ftp/Computation/monads.html#LogicT _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe