Hi Emil,

The reason has to do with the definitions of (>>=) for Writer and
(WriterT m).  Looking at Control.Monad.Writer (ghc-6.2.2),

newtype Writer w a = Writer { runWriter :: (a, w) }

instance (Monoid w) => Monad (Writer w) where
        m >>= k  = Writer $ let
                (a, w)  = runWriter m
                (b, w') = runWriter (k a)
                in (b, w `mappend` w')

newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }

instance (Monoid w, Monad m) => Monad (WriterT w m) where
        return a = WriterT $ return (a, mempty)
        m >>= k  = WriterT $ do
                (a, w)  <- runWriterT m
                (b, w') <- runWriterT (k a)
                return (b, w `mappend` w')

Patterns in "let" expressions bind lazily, so Writer's (>>=) is lazy
in both its arguments and thus can handle the infinite recursion of
your "foo".  However, patterns in "do" expressions bind strictly, so
WriterT's (>>=) is strict in its arguments; it tries to evalue "foo"
completely, causing a stack overflow.

You may use "case" expressions instead of "let" statements to bind
patterns strictly.  Conversely,  you can also make a do statement bind
patterns lazily, using lazy patterns (see eg
http://www.cs.sfu.ca/CC/SW/Haskell/hugs/tutorial-1.4-html/patterns.html#tut-lazy-patterns)


Hope that helps,
-Judah


On Tue, 15 Feb 2005 17:45:26 +0100, Emil Axelsson <[EMAIL PROTECTED]> wrote:
> Hello,
> 
> I have a huge space leak in a program due to laziness in the writer monad. Now
> when I'm trying to examine the behaviour of writer I get a bit puzzled by the
> following program:
> 
>     foo :: MonadWriter [Int] m => Int -> m ()
>     foo n = do tell [n]
>                foo $ n+1
> 
>     test  = (snd $ runWriter $ foo 0) !! 3
> 
>     testT = (snd $ runIdentity $ runWriterT $ foo 0) !! 3
> 
> I would expect both test and testT to terminate with the value 3, due to the
> laziness that caused me problems. But here is the actual run results:
> 
>     Ok, modules loaded: Main.
>     *Main> test
>     3
>     *Main> testT
>     *** Exception: stack overflow
>     *Main>
> 
> Could someone please explain this to me?
> 
> / Emil
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to