[Haskell-beginners] How does this function append the log to the beginning of the list?

Daniel Fischer daniel.is.fischer at googlemail.com
Mon Dec 24 16:49:47 CET 2012


On Montag, 24. Dezember 2012, 06:47:34, jugree at lavabit.com wrote:
> Hello.
> 
> Could you explain this example(0)? Could you show its step by step
> execution?
> 
> gcd' :: Int -> Int -> Writer (DiffList String) Int
> gcd' a b
>     | b == 0 = do
>         tell (toDiffList ["Finished with " ++ show a])
>         return a
>     | otherwise = do
>         result <- gcd' b (a `mod` b)
>         tell (toDiffList [show a ++ " mod " ++ show b ++ " = " ++ show (a
> `mod` b)])
>         return result
> 
> Why does the above append the log to the beginning of the list?

It doesn't. Note that it first computes the gcd of b and (a `mod` b), logging 
the steps, and only afterwards "tell"s the original arguments. So the very 
first thing that is logged is the "Finished with" message.

gcd' 3 2            -- nothing logged yet
  gcd' 2 1          -- nothing logged yet
    gcd' 1 0        -- start logging
      tell (["Finished with 1"]++)
      return 1      -- log is (["F. w. 1"]++)
    tell (["2 mod 1 = 0"]++)
    return 1        -- log is ((["F. w. 1"]++) . (["2 mod 1 = 0"]++))
  tell (["3 mod 2 = 1"]++)
  return 1
   -- log is (((["F. w. 1"]++) . (["2 mod 1 = 0"]++)) . (["3 mod 2 = 1"]++))

> 
> What value will result have in the following?
> 
> result <- gcd' 2 (3 `mod` 2)

result will be bound to 1 (the value of gcd 2 1).

Basically, a `Writer monoid a` is a pair `(a, monoid)` and the monadic bind 
`(>>=)` that the do-notation desugars to is

    (x,log) >>= f
      = let (y, newLog) = f x
        in (y, log `mappend` newLog)

so

   do result <- gcd' 2 (3 `mod` 2)
      tell (["3 mod 2 = 1"]++)
      return result

becomes

  gcd' 2 1 >>= \result -> (tell (...) >> return result)

and substituting gcd' 2 1 with its result:

    (1,log) >>= \result -> (tell (...) >> return result)

  ~> let (y, newLog) = (\result -> (tell (...) >> return result)) 1
     in (y, log <> newLog)
  ~> let (y, newLog) = tell (...) >> return 1
     in (y, log <> newLog)
  ~> let (y, newLog) = let (_, told) = tell (...)
                       in (1, mempty <> told)
     in (y, log <> newLog)

> 
> (0) http://learnyouahaskell.com/for-a-few-monads-more#writer
> 



More information about the Beginners mailing list