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

Paolino paolo.veronelli at gmail.com
Thu Jan 1 02:01:57 EST 2009


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


2008/12/31 Derek Elkins <derek.a.elkins at gmail.com>

> 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.
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090101/bea54add/attachment.htm


More information about the Haskell-Cafe mailing list