
IO is not lazy; you never make it to "print". Consider this program:
k = f 0 where f n = do lift (print n) tell [n] f (n+1)
weird :: IO [Int] weird = do (_, ns) <- runWriterT k return (take 20 ns)
What should "weird" print? According to "k", it prints every Int from
0 up. Aside from the extra printing, it has the same behavior as your
writer.
For the result of a WriterT to be lazy readable, you need both the
monoid to be lazy readable, and the transformed monad to be lazy,
which IO isn't.
-- ryan
2008/12/31 Paolino
As someone suggested me, I can read the logs from Writer and WriterT as computation goes by, if the monoid for the Writer is lazy readable. This has been true until I tried to put the IO inside WriterT
{-# LANGUAGE FlexibleContexts #-} import Control.Monad.Writer
k :: (MonadWriter [Int] m) => m [Int]
k = let f x = tell [x] >> f (x + 1) in f 0
works :: [Int] works = snd $ runWriter k
hangs :: IO [Int] hangs = snd `liftM` runWriterT k
main = take 20 `liftM` hangs >>= print
The main hangs both interpreted and compiled on ghc 6.10.1.
The issue is not exposing with IO alone as
main = print "test" >> main
is a working program.
Thanks for explanations.
paolino
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe