debug: Simple trace-based debugger

[ bsd3, debugging, development, library, program ] [ Propose Tags ]

An easy to use debugger for viewing function calls and intermediate variables. To use, annotate the function under test, run the code, and view the generated web page. Full usage instructions are at Debug.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0, 0.0.1, 0.0.2, 0.1, 0.1.1
Change log CHANGES.txt
Dependencies ansi-wl-pprint, base (>=4 && <5), containers, directory, extra, ghc-prim, js-jquery, open-browser, template-haskell, uniplate [details]
License BSD-3-Clause
Copyright Neil Mitchell 2017
Author Neil Mitchell <ndmitchell@gmail.com>
Maintainer Neil Mitchell <ndmitchell@gmail.com>
Category Development, Debugging
Home page https://github.com/ndmitchell/debug
Bug tracker https://github.com/ndmitchell/debug/issues
Source repo head: git clone https://github.com/ndmitchell/debug.git
Uploaded by NeilMitchell at 2017-12-18T23:24:02Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 3559 total (19 in the last 30 days)
Rating 2.5 (votes: 3) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2017-12-20 [all 4 reports]

Readme for debug-0.0.2

[back to package description]

Haskell Debugger Hackage version Stackage version Linux Build Status Windows Build Status

A library for debugging Haskell programs. To use, take the functions that you are interested in debugging, e.g.:

module QuickSort(quicksort) where
import Data.List

quicksort :: Ord a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort lt ++ [x] ++ quicksort gt
    where (lt, gt) = partition (<= x) xs

Turn on the TemplateHaskell and ViewPatterns extensions, import Debug, indent your code and place it under a call to debug, e.g.:

{-# LANGUAGE TemplateHaskell, ViewPatterns #-}
module QuickSort(quicksort) where
import Data.List
import Debug

debug [d|
   quicksort :: Ord a => [a] -> [a]
   quicksort [] = []
   quicksort (x:xs) = quicksort lt ++ [x] ++ quicksort gt
       where (lt, gt) = partition (<= x) xs
   |]

We can now run our debugger with:

$ ghci QuickSort.hs
GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling QuickSort        ( QuickSort.hs, interpreted )
Ok, 1 module loaded.
*QuickSort> quicksort "haskell"
"aehklls"
*QuickSort> debugView

The call to debugView starts a web browser to view the recorded information, looking something like:

Debug view output

Limitations

This tool is quite new, so it has both limitations, places it is incomplete and bugs. Some notable issues:

  • It calls show on all the values in encounters, meaning they must all have a Show instance (it defines a global Show instance which should get used as a fallback), and they will be fully evaluated. If your program relies on laziness it probably won't work.
  • It doesn't really understand shadowed variables, so it will work, but the debug results will be lower quality.
  • For function values it won't give you a whole lot of information.

Alternatives

For practical alternatives for debugging Haskell programs you may wish to consider:

  • GHCi debugger, simple imperative-style debugger in which you can stop a running computation in order to examine the values of variables. The debugger is integrated into GHCi. Robust, reliable, somewhat difficult to use.
  • Hood and Hoed, a value-based observational debugger with a difficult user interface, deals well with laziness.
  • Hat, good ideas, but I've never got it working.

Compared to the above, debug stresses simplicitly of integration and user experience.

FAQ

Q: debugView fails talking about Wine?

A: If you get wine: invalid directory "/home/f/.wine" in WINEPREFIX: not an absolute path when running debugView that means xdg-open is handled by Wine. Fix that and it will work once more.