Nils Anders Danielsson <[EMAIL PROTECTED]> writes:
> My program is failing with head [], or an array bounds error, or some
> other random error, and I have no idea how to find the bug. Can you
> help?
>
> Compile your program with -prof -auto-all (make sure you have the
> profiling libraries installed), and run it with +RTS -xc -RTS to
I also have experienced - ahem - varying results with -xc. My
solution is to use 'ghc -cpp' instead, and something like the following:
import Prelude hiding (head,read)
/* ugly, but a real functon would block subsequent imports */
#define BUG(C_,M_) (error ("Program error - '"++C_++"' failed: "++M_++".
Location: "++__FILE__++" line: "++ show __LINE__))
#define head (\xs -> case xs of { (x:_) -> x ; _ -> BUG("head","empty list")})
#define at (let {at_ (y:_) 0 = y; at_ (y:ys) n = if n>0 then at_ ys (n-1)
else BUG("at","negative index"); at_ _ _ = BUG ("at","index too large")} in \a
x -> at_ a x)
#define read (\s -> case [ x | (x,t) <- reads s, ("","") <- lex t] of { [x]
-> x ; [] -> BUG("read","no parse"); _ -> BUG("read","ambigous parse")})
#define fromJust (\x -> case x of Just a -> a; Nothing ->
BUG("fromJust","Nothing"))
#define undefined (error ("Hit 'undefined' in "++__FILE__++", "++show
__LINE__))
This redefines a bunch of "difficult" functions to report file name
and line number, instead of just an anonymous error message. It won't
work for (infix, non-alpha) operators -- like array indexing -- or
identifiers with apostrophes, unfortunately.
-k
--
If I haven't seen further, it is by standing in the footprints of giants
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe