
Hello *, frequently we are seeing messages like "List.head: empty list" or "Maybe.fromJust: Nothing". It is clear what happened and where the messages were triggered yet the real cause is usually VERY hard to find unless the program is small and simple. I came to the conclusion that functions like head and fromJust are best to be avoided because their use may render large programs unmaintainable. Instead I use irrefutable pattern matching like (x : _) = l and Just bla = maybeBla whenever possible because when a pattern match fails the ghc runtime system gives me a nice error message naming the module, line and column. However, this procedure may become tedious when the error occurs in a call to a third-party library function. I wonder whether it is possible to print a "closure trace" similar to a stack trace in procedural programming. Say we have two modules A and B: module A where import B a = b module B b = c where c = error "go to hell" I would like to see something like this: sh$ ghci A <ghci startup messages> > a Runtime error "go to hell" in module B at line 2 Trace: B.b.c B.b A.a This way it would be easy to find the reason that actually caused, say, head to fail. I guess it would be sufficient to complement closures with information on the precise place of their definition. Michael

Hello Michael, Wednesday, June 14, 2006, 1:19:03 PM, you wrote:
frequently we are seeing messages like "List.head: empty list" or "Maybe.fromJust: Nothing". It is clear what happened and where the
one time i complained the close problem SPJ answered me (see ghc-users mail-list at 23 may 2005): | also it will be cool to have ability to add such annotations to my own | functions, smthg like: | | head (x:xs) = x | head [] = superError "head []" | | which will print: "Error: head [] in Module.hs:155" A difficulty is that the caller of 'head' might itself be called from somewhere else: foo (xs, ys) = head xs It's not much help to know that head failed when called from foo; you want to know where foo is called from. In short, you really want the whole call stack. But trimmed in the recursive case... It's all very like cost-centre stacks, which is why GHC provides the -xc option when you are profiling. I think that give you what you want --- but you have to compile your program profiled. Another take on this is that you want an implicit parameter head :: (%loc :: Location) => [a] -> a so that 'head' can report %loc when it fails. Now you'd need to give rules to say where %loc is bound. It'd be a pretty magic kind of implicit parameter. Or should it be a stack of locations? I'm not belittling the underlying problem, which is real. But there do seem to be many possible design choices without an obvious optimium. If someone can boil out a principled and simple solution, it'd be a good contribution. Simon
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin
I'm not belittling the underlying problem, which is real. But there do seem to be many possible design choices without an obvious optimium. If someone can boil out a principled and simple solution, it'd be a good contribution.
You can also use CPP macros for the worst offenders. Something like (untested, but you get the idea): #define BUG(X) (error (X++" failed, __FILE__,__LINE__") #define head (\x -> case x of (x:_) -> x; _ -> BUG("head")) #define fromJust ... It's also worthwhile to check out the darcs code for some fancy bug/error handling. -k -- If I haven't seen further, it is by standing in the footprints of giants

Hi Michael,
I have defined fromJustNote and headNote, which take an extra
parameter, for example:
fromJustNote msg (Just x) = x
fromJustNote msg Nothing = error $ "fromJustNote failed, " ++ msg
I also have lookupJust which does a lookup and a fromJust, since this
is a common pattern in my program, and if the lookup fails I can show
the key, which usually gives me a clue as to what went wrong - rather
than fromJust Nothing which has no useful information.
I found that this is a really useful thing to do as programs get
bigger - when I get a fromJust error I just run around replacing
fromJust's to fromJustNote's and wait til I catch the error.
The other thing to do is use Hat (http://www.haskell.org/hat) to
generate a hat-trace then use hat-stack, which does exactly what you
ask for and more.
Thanks
Neil
On 6/14/06, Michael Marte
Hello *,
frequently we are seeing messages like "List.head: empty list" or "Maybe.fromJust: Nothing". It is clear what happened and where the messages were triggered yet the real cause is usually VERY hard to find unless the program is small and simple. I came to the conclusion that functions like head and fromJust are best to be avoided because their use may render large programs unmaintainable. Instead I use irrefutable pattern matching like (x : _) = l and Just bla = maybeBla whenever possible because when a pattern match fails the ghc runtime system gives me a nice error message naming the module, line and column. However, this procedure may become tedious when the error occurs in a call to a third-party library function.
I wonder whether it is possible to print a "closure trace" similar to a stack trace in procedural programming. Say we have two modules A and B:
module A where import B a = b
module B b = c where c = error "go to hell"
I would like to see something like this:
sh$ ghci A <ghci startup messages> > a
Runtime error "go to hell" in module B at line 2 Trace: B.b.c B.b A.a
This way it would be easy to find the reason that actually caused, say, head to fail.
I guess it would be sufficient to complement closures with information on the precise place of their definition.
Michael _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Michael,
On 6/14/06, Michael Marte
I wonder whether it is possible to print a "closure trace" similar to a stack trace in procedural programming. Say we have two modules A and B:
I wrote small (external) utility that does something like that for
ghc-built binaries.
It can print traces on user defined breakpoints. As there isn't much
use for it,
I haven't played with a while, but it might help or provide starting point.
darcs get http://tamelambda.net/darcs/tracer/
(requires ghc 6.4.2 and Windows to compile and use)
Example output for tracing "lines", of a program something like this:
getContents >>= mapM_ putStrLn . lines
Trace: Data.List.lines + 0

Michael Marte wrote:
frequently we are seeing messages like "List.head: empty list" or "Maybe.fromJust: Nothing". It is clear what happened and where the messages were triggered yet the real cause is usually VERY hard to find unless the program is small and simple. I came to the conclusion that functions like head and fromJust are best to be avoided because their use may render large programs unmaintainable. Instead I use irrefutable pattern matching like (x : _) = l and Just bla = maybeBla whenever possible because when a pattern match fails the ghc runtime system gives me a nice error message naming the module, line and column. However, this procedure may become tedious when the error occurs in a call to a third-party library function.
I wonder whether it is possible to print a "closure trace" similar to a stack trace in procedural programming.
Try compiling for profiling (-prof -auto-all) and running with +RTS -xc. If you're lucky, you'll get a stack trace. The GHCi debugging project that Pepe Iborra is working on (Google summer of code) might address this issue, too. Cheers, Simon
participants (6)
-
Bulat Ziganshin
-
Esa Ilari Vuokko
-
Ketil Malde
-
Michael Marte
-
Neil Mitchell
-
Simon Marlow