[Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

Thomas Hartman tphyahoo at gmail.com
Sun Feb 10 18:33:41 EST 2008


The following is a simple introduction to debugging techniques in
haskell, illustrated with a canonical use of foldr and foldl.

Comments welcome.

import Control.Monad.Writer
import Debug.Trace
-- We use the writer monad to better understand foldl and foldr
-- and show a debugging technique in haskell
-- you could get similar output using Debug.Trace, but this relies on
unsafePerformIO
-- ... http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/Debug-Trace.html
-- which is Ugly.
-- Though ugly, trace isn't really unsafe as far as my understanding
goes. But still, I find it nice
-- that there's a way to accomplish the exact same thing by using the
writer or "debugger" monad
-- which is pure as pure can get

-- In this particular example, it doesn't matter if you use
Debug.Trace or the writer monad.
-- However, I am fidding around in another scenario (debugging a
series of graphs using Data.Graph.Inductive)
-- which seems not to lend itself well to trace. If I can find a nice
way to explain what I am doing and why
-- I may do a follow-up to this post describing that.

-- same as prelude, I think
myfoldr f z []     =  z
myfoldr f z (x:xs) =  x `f` r
  where r = (myfoldr f z xs)
myfoldl f z [] = z
myfoldl f z (x:xs) = myfoldl f l xs
  where l = z `f` x

-- canonical uses of fold, no debug output
tfr = myfoldr (:) [] [1..10] -- copy a list
tfl = myfoldl (flip (:)) [] [1..10] -- reverse a list

-- debugging output using Debug.Trace (unsafePerfomIO)
-- (Not really unsafe, but unsafePerformIO (which is used in the trace
function) sounds kind of scary)
myfoldrD f z [] =  z
myfoldrD f z (x:xs) | trace ("x,r: " ++ (show (x,r))) True =  x `f` r
  where r = (myfoldrD f z xs)
myfoldlD f z [] = z
myfoldlD f z (x:xs) | trace (("z,x") ++ (show (z,x))) True= myfoldlD f l xs
  where l = z `f` x

-- run these to see the functions with debug output from trace
tfrD = myfoldrD (:) [] [1..10] -- copy a list
tflD = myfoldlD (flip (:)) [] [1..10] -- reverse a list

-- using writer monad
-- Nothing unsafe here, pure referrentially transparent goodness
myfoldrW f z []     =  return z
myfoldrW f z (x:xs) = do
    r <- (myfoldrW f z xs)
    tell ("x,r: " ++ (show (x,r)) ++ "\n" )
    return $ x `f` r

myfoldlW f z [] = return z
myfoldlW f z (x:xs) = do
  tell ("z,x): " ++ (show (z,x)) ++ "\n")
  l <- return $ (z `f` x)
  myfoldlW f l xs

-- display the debug output from the writer monad
tfrW = putStrLn $ snd $ runWriter $ myfoldrW (:) [] [1..10]
tflW = putStrLn $ snd $ runWriter $ myfoldlW (flip (:)) [] [1..10]


More information about the Haskell-Cafe mailing list