'Nice' Debugging?

Are there any nice ways to use Debug.Trace functions?

(it’s a bit of an oxymoron, I know!)

Small problem: if I insert them into my code, and want to uncomment them I usually also have to worry about whitespace again (maybe an auto formatter is a good idea).

Quite happy I have gone a long time without them, but they are handy also.

2 Likes

One trick I learned a while ago is to use ' to differentiate between traced function and untraced one. Say i have foo with some args and I want to debug it. I will change code from

foo ... = ... foo ... -- first pattern match, recursive call
foo ... = ...         -- another pattern match

to

foo ... = traceShow (..., ..., ...) $ foo' ...  -- put the arguments in the tuple and then call the original function
foo' ... = ... foo ... -- first pattern match, recursive call
foo' ... = ...         -- another pattern match

This way, I don’t need to change te rest of the code and can quickly remove tracing by commenting the first line and removing the 's

6 Likes

One trick I use often is to add a bogus guarded case to functions:

fib n | trace ("fib " ++ show n) False = undefined
fib 0 = 0
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)
24 Likes

Usually, I manage to make trace a full line, so I just have to comment the line.
Do you have any example ?

2 Likes

Yes

foo = <lots of code>
    where !() = trace ("Something: " ++ show importantVariable) ()

(Always use where !() not where !_ otherwise you risk writing trace s instead of trace s () and the former doesn’t produce any output!)

16 Likes

There’s fancy wrappers in Hledger.Utils.Debug.

5 Likes

Albert Lai has a page on Debug.Trace which includes the following idiom:

If I am tired of writing “traceShow n” 3 times (and later deleting them thoroughly), here is a cool trick:

import Debug.Trace

f n | traceShow n False = undefined
f n | n <= 1 = n
    | r == 0 = f q
    | otherwise = f (3*n + 1)
  where
    (q, r) = n `divMod` 2

Explanation: A new case that the computer must check first, which will be summarily rejected anyway, but it’s the journey of printing n that matters.

Benefits: easy and unintrusive to add, and easy to delete later.

8 Likes

I’m not sure it counts as nice but I often add debug and performance stuff in as (the lazy) StateT, and then you can flip between evalStateT for non-debug and runStateT for debug, without having to erase the debug code.

4 Likes

Could you give an example ?

1 Like

PerfT is used for performance measurement, but you could generalize the idea.

https://hackage.haskell.org/package/perf-0.12.0.0/docs/Perf-Types.html

2 Likes

This is better than my trick, one single line to comment out to disable tracing instead of also needing to remove 's. Thanks

I’m new to Haskell coming from Python where I use print debugging frequently. I’m glad I found this page because there are some excellent suggestions here!

I often want to add a label to a traced value. Currently, I’m using this function:

debug :: Show a => String -> a -> a
debug label expr = trace (label ++ " " ++ show expr) expr

which can be used inline like this:

fac :: (Show t, Eq t, Num t) => t -> t
fac 0 = 1
fac n = debug "n" n * fac (n-1)

I really wish this function was defined in Debug.Trace.

2 Likes

I think I’d suggest instead

{-# LANGUAGE BangPatterns #-}

fac :: (Show t, Eq t, Num t) => t -> t
fac 0 = 1
fac n = n * fac (n-1)
  where !() = traceShow ("n", n) ()

This has at least two benefits over your debug: it doesn’t require defining a new debug combinator, and it’s a single line that can be added or deleted freely without changing the actual functional code.

2 Likes

As @tomjaguarpaw suggested you can use traceShow and tuples, so you can do things like

fac n = traceShow("n", n, "result", r) where r =
           n * fact ( n - 1)

I put two lines so that you can easily delete traceShow ... r = later on.

1 Like