[Haskell-cafe] Debug tracing in Haskell

Alex Belanger i.caught.air at gmail.com
Wed Nov 23 15:32:04 UTC 2016


I personally prefer the approach in this package:

https://hackage.haskell.org/package/NoTrace

You import Debug.Trace when you want traces and switch the import to
Debug.NoTrace to disable them.

You could use a similar strategy with verbosity levels; plus you might not
even need levels, as this is module-based you don't get the extra noise
from other modules.

- nitrix

On Nov 22, 2016 4:11 PM, "Edward Z. Yang" <ezyang at mit.edu> wrote:

> Hello Clinton,
>
> Just to clarify, you are asking how to toggle traceability on a
> per-module (or perhaps per-package) basis?  Because if you're
> OK with tracing be a global affair then putting everything in
> a package works quite well (you can use a flag to control
> whether or not you want to build with or without tracing.)
>
> Edward
>
> Excerpts from Clinton Mead's message of 2016-11-23 00:37:57 +1100:
> > I've been debugging some Haskell code, including a lot of work on Mutable
> > Vectors, so naturally I've found `trace` useful, and in particular
> > `traceM`, because it fits in nicely with monadic code.
> >
> > The problem is that unlike `assert`, both `trace` and `traceM` execute
> > unconditionally, I can't toggle them with a compiler flag.
> >
> > I could however do something like this in every file I want to do
> tracing.
> >
> > {-# LANGUAGE CPP #-}
> >
> > #ifdef TRACE
> > trace = Debug.Trace.trace
> > traceM = Debug.Trace.traceM
> > #else
> > trace _ = id
> > traceM _ = pure ()
> > #endif
> >
> > But already, that's a lot of boilerplate.
> >
> > I'd also like to trace based on debug levels. For example, at TRACE level
> > 2, only print trace statements at level 1 or 2, but at TRACE level 4,
> print
> > trace statements at level 1, 2, 3 and 4, providing more detail (but more
> > noise).
> >
> > This makes the above code even more complex.
> >
> > This wouldn't be a problem if I could put the code in a separate package,
> > but I can't, as then whether tracing is on or not depends on the compiler
> > settings of the tracing package, not on the calling package, which
> defeats
> > the purpose somewhat.
> >
> > I considered using implicit parameters to quietly pass whether I want
> > tracing and at what level into the tracing module, but it seems to be
> that
> > implicit parameters can't be defined at the top level.
> >
> > It gets even more complex. When debugging, I might want to print
> something
> > of type 'a'. Obviously 'a' will need some sort of show method for this to
> > work, but outside of debug mode I don't want to restrict my function's
> > types to things which are showable. So I considered doing this:
> >
> > #ifdef TRACE
> > type DebugShow a = Show a
> > debugShow = show
> > #else
> > type DebugShow a = ()
> > debugShow _ = error "DEBUG SHOWING OUTSIDE OF DEBUG MODE"
> > #endif
> >
> > And of course, if you're only using `debugShow` as part of an argument to
> > `trace`, lazy evaluation will avoid `debugShow` ever being called when
> > tracing is not enabled.
> >
> > But put all this together and you've got around a dozen lines of
> > boilerplate just to do tracing, without even having tracing levels yet,
> > that have to be put in every module you want to use tracing, but don't
> want
> > a whole lot of debug data being spat out in a release compile.
> >
> > Also, adding any other tracing functions just makes this longer.
> >
> > The only approach I can think of so far is to whack this all in a
> template
> > haskell module and add code that splices it all into the current module:
> >
> > e.g.
> >
> > #ifdef TRACE
> > $(traceFunctions True)
> > #else
> > $(traceFunctions False)
> > #endif
> >
> > Where `traceFunctions` is a template haskell function that dumps all the
> > appropriate functions and type definitions mentioned above (and maybe
> more)
> > at the top level of the calling module.
> >
> > So my questions are:
> >
> > 1. Is there a better way? And
> > 2. Has this problem already been solved?
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20161123/9d376d9f/attachment.html>


More information about the Haskell-Cafe mailing list