[Haskell-beginners] LYAH Control.Monad.Writer tell

David McBride toad3k at gmail.com
Mon Jan 16 08:52:36 CET 2012


Reading that chapter, he seemed to have veered off course at some
point.  He started having you implement your own simple writer type,
but he stopped short of actually making it usable, then he started
showing you how you would use the real writer class.  Unless I'm
mistaken, he also didn't tell you how to reimplement logNumber with
the real library, so of course the code didn't work.

So the tell class is part of the MonadWriter class, which he didn't
explain the point of (along with listen).  Tell just takes a list of
things and adds them to the list of things you have.  The reason why
his Writer class has a tuple, is that in addition to concatenating log
messages, when you do a return from runWriter, you will get a first
argument in a tuple.  That argument ends up being the last item that
was returned or the last value returned from any monad passed as an
argument into listen.

Why would it do that?  Well I don't think it is used very often (or
possibly at all), but originally the idea was that the writer monad
can encompass both the ability to track what has happened in a program
and also its final return value.  I'm having trouble thinking of a use
for it, perhaps returning a failure code from a compilation, as well
as the log of messages?  Generally if you wanted to keep state you
would use the state monad for something like that, which allows you to
query it as well as set it.

The actual running code that you would have at that point in the book would be:

import Data.Monoid
import Control.Monad.Writer

logNumber :: Int -> Writer [String] Int
logNumber x = do
  tell ["Got number: " ++ show x]
  return x

multWithLog :: Writer [String] Int
multWithLog = do
    a <- logNumber 3
    b <- logNumber 5
    tell ["Gonna multiply these two"]
    return (a*b)

main = putStrLn . show $ runWriter multWithLog

which returns
(15,["Got number: 3","Got number: 5","Gonna multiply these two"])

On Sun, Jan 15, 2012 at 8:07 PM, TJ Takei <tj.takei at gmail.com> wrote:
> Hi
>
> I have a trouble to run an example of "Learn Your A Haskell.." Chap 13
> below:
>
> ========
> import Data.Monoid
> --Don't import Control.Monad.Writer
>
> newtype Writer w a = Writer { runWriter :: (a, w) }
>
> instance (Monoid w) => Monad (Writer w) where
>     return x = Writer (x, mempty)
>     (Writer (x,v)) >>= f = let (Writer (y, v')) = f x in Writer (y, v
> `mappend` v')
>
> --Define tell
> tell :: [String] -> Writer [String] Int
> tell w = Writer (0, w)  -- what'sa hell "0" for ???!!!
>
> logNumber :: Int -> Writer [String] Int
> logNumber x = Writer (x, ["Got number: " ++ show x])
>
> multWithLog :: Writer [String] Int
> multWithLog = do
>     a <- logNumber 3
>     b <- logNumber 5
>     tell ["Gonna multiply these two"]
>     return (a*b)
>
> main = putStrLn . show $ runWriter multWithLog
> ========
>
> I changed two places to run it without error:
> [1] Ambiguity error of Writer, uneless I comment out "import
> Control.Monad.Writer", and
> [2] Define tell function
>
> My questions are:
> Why does LYAH sample fail as is?
> Do the changes above look reasonable?
> I'm not certain about my "tell". Where is the correct instantiation of
> "tell" included?
>
> Thanks,
> TJ
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list