[Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

Derek Elkins derek.a.elkins at gmail.com
Wed Dec 31 15:59:52 EST 2008


On Wed, 2008-12-31 at 21:48 +0100, Paolino wrote:
> 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  

runWriterT :: MonadWriter w m a => WriterT w m a -> m (a, w)

which is to say runWriterT k :: IO (a, [Int])

It's not going to return anything until the IO action terminates, which is to say never.



More information about the Haskell-Cafe mailing list