Hierarchical tracing for debugging laziness

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/

Great, It illustrates why difference lists are awesome.
import HTrace
app :: [a] -> [a] -> [a]
app [] ys = htrace "app" ys
app (x:xs) ys = htrace "app" (x:app xs ys)
rev1 [] = htrace "[]" []
rev1 (x:xs) = htrace "rev1" (app (rev1 xs) [x])
rev2 [] ys = htrace "ys" ys
rev2 (x:xs) ys = htrace ":" (rev2 xs (x:ys))
*Main> rev1 [1..10]
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
[]
app
app
app
app
app
app
app
app
app
app
[10app
app
app
app
app
app
app
app
app
,9app
app
app
app
app
app
app
app
,8app
app
app
app
app
app
app
,7app
app
app
app
app
app
,6app
app
app
app
app
,5app
app
app
app
,4app
app
app
,3app
app
,2app
,1]
*Main> rev2 [1..10]
<interactive>:4:1:
No instance for (Show ([a0] -> [a0]))
arising from a use of `print'
Possible fix: add an instance declaration for (Show ([a0] -> [a0]))
In a stmt of an interactive GHCi command: print it
*Main> rev2 [1..10] []
:
:
:
:
:
:
:
:
:
:
ys
[10,9,8,7,6,5,4,3,2,1]
Thanks for sharing!
On 25 January 2012 01:47, Eugene Kirpichov
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/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks! I released it: http://hackage.haskell.org/package/htrace http://github.com/jkff/htrace On Wed, Jan 25, 2012 at 4:18 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Really nice! Looks like it could be a useful mini-package on Hackage.
-- Felipe.
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

Hi, nice little package! I just made a fork and added a new function makeHTrace to be able to have separate variables 'level'. I also add the htrace type signature (or else haddock won't generate documentation for this module): https://github.com/YwenP/htrace I was also investigating in a way to fix an annoyment. You see, in GHCI:
let {a = htrace "a" 12; b = htrace "b" 29; c = htrace "c" 10; d = htrace "d" 90; x = htrace "," (htrace "+" (a+b), htrace "*" (c*d)) } x
prints:
,
(+
a
b
41,*
c
d
900)
Instead, we'd like to have (if I'm right):
,
+
a
b
*
c
d
(41,900)
But I haven't found a way to tell GHCI to fully evaluate 'x' but _not_
print its value.
2012/1/25 Eugene Kirpichov
Thanks!
I released it:
http://hackage.haskell.org/package/htrace http://github.com/jkff/htrace
On Wed, Jan 25, 2012 at 4:18 AM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Really nice! Looks like it could be a useful mini-package on Hackage.
-- Felipe.
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Jan 25, 2012 at 7:38 PM, Yves Parès
But I haven't found a way to tell GHCI to fully evaluate 'x' but _not_ print its value.
let {a = htrace "a" 12; b = htrace "b" 29; c = htrace "c" 10; d = htrace "d" 90; x = htrace "," (htrace "+" (a+b), htrace "*" (c*d)) } :force x ,
Use the :force, Yves! + a b * c d x = (41,900) Cheers! =) -- Felipe.

One day, I _really_ should learn all GHCI commands... Thanks, Felipe ^^ 2012/1/25 Felipe Almeida Lessa> On Wed, Jan 25, 2012 at 7:38 PM, Yves Parès wrote: > > But I haven't found a way to tell GHCI to fully evaluate 'x' but _not_ > print > > its value. > > Use the :force, Yves! > > > let {a = htrace "a" 12; b = htrace "b" 29; c = htrace "c" 10; d = htrace > "d" 90; x = htrace "," (htrace "+" (a+b), htrace "*" (c*d)) } > > :force x > , > + > a > b > * > c > d > x = (41,900) > > Cheers! =) > > -- > Felipe. >

Look how one can watch the evaluation tree of a computation, to debug laziness-related problems.
You might like the old Hood/GHood: http://hackage.haskell.org/package/hood http://hackage.haskell.org/package/GHood Background info/papers: http://www.ittc.ku.edu/csdl/fpg/Tools/Hood http://www.ittc.ku.edu/csdl/fpg/node/26 http://community.haskell.org/~claus/GHood/ Claus
participants (5)
-
Claus Reinke
-
Eugene Kirpichov
-
Felipe Almeida Lessa
-
HASHIMOTO, Yusaku
-
Yves Parès