[Haskell-cafe] Hierarchical tracing for debugging laziness
Eugene Kirpichov
ekirpichov at gmail.com
Tue Jan 24 17:47:11 CET 2012
Hi cafe,
Look how one can watch the evaluation tree of a computation, to debug
laziness-related problems.
{-# LANGUAGE BangPatterns #-}
module HTrace where
import Data.List (foldl')
import Data.IORef
import System.IO.Unsafe
level = unsafePerformIO $ newIORef 0
htrace str x = unsafePerformIO $ do
lvl <- readIORef level
putStrLn (replicate (4*lvl) ' ' ++ str)
writeIORef level (lvl+1)
let !vx = x
writeIORef level lvl
return vx
xs = map (\x -> htrace (show x) x) [1..10]
s = foldl (\a b -> htrace "+" (a+b)) 0 xs
s2 = foldl' (\a b -> htrace "+" (a+b)) 0 xs
b = htrace "b" 2
c = htrace "c" 3
a = htrace "a" $ b + c
x = htrace "x" $ b + c
*HTrace> a
a
b
c
5
*HTrace> x
x
5
*HTrace> s
+
+
+
+
+
+
+
+
+
+
1
2
3
4
5
6
7
8
9
10
55
(reload)
*HTrace> s2
+
1
+
2
+
3
+
4
+
5
+
6
+
7
+
8
+
9
+
10
55
--
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120124/b46aae4d/attachment.htm>
More information about the Haskell-Cafe
mailing list