| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Debug.Hoed
Description
An alternative backend for lazy debugging with call stacks built on top of the Hoed package.
Instrumentation is done via a TH wrapper, which requires the following extensions:
Moreover, Observable instances are needed for value inspection. The debug' template haskell wrapper can automatically insert these for Generic types.
{-# LANGUAGE TemplateHaskell, ViewPatterns, PartialTypeSignatures, ExtendedDefaultRules #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
module QuickSort(quicksort) where
import Data.List
import Debug.Hoed
debug [d|
quicksort :: Ord a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort lt ++ [x] ++ quicksort gt
where (lt, gt) = partition (<= x) xs
|]Now we can debug our expression under debugRun:
$ ghci examples/QuickSortHoed.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling QuickSortHoed ( QuickSortHoed.hs, interpreted ) Ok, 1 module loaded. *QuickSort> debugRun $ quicksort "haskell" "aehklls"
After our expression is evaluated a web browser is started displaying the recorded information.
To debug an entire program, wrap the main function below debugRun.
- debug :: Q [Dec] -> Q [Dec]
- debug' :: Config -> Q [Dec] -> Q [Dec]
- data Config = Config {}
- debugRun :: IO () -> IO ()
- getDebugTrace :: HoedOptions -> IO () -> IO DebugTrace
- debugPrintTrace :: DebugTrace -> IO ()
- debugJSONTrace :: DebugTrace -> ByteString
- debugViewTrace :: DebugTrace -> IO ()
- debugSaveTrace :: FilePath -> DebugTrace -> IO ()
- class Observable a where
- observe :: Observable a => Text -> a -> a
- data HoedOptions :: * = HoedOptions {
- verbose :: Verbosity
- prettyWidth :: Int
- defaultHoedOptions :: HoedOptions
Documentation
debug :: Q [Dec] -> Q [Dec] Source #
A TemplateHaskell wrapper to convert normal functions into traced functions.
debug' :: Config -> Q [Dec] -> Q [Dec] Source #
A TemplateHaskell wrapper to convert normal functions into traced functions
and optionally insert Observable and Generic instances.
Constructors
| Config | |
Fields
| |
debugRun :: IO () -> IO () Source #
Runs the program collecting a debugging trace and then opens a web browser to inspect it.
main = debugRun $ do
...
Generate a trace
getDebugTrace :: HoedOptions -> IO () -> IO DebugTrace Source #
Runs the program collecting a debugging trace
Trace commands
debugPrintTrace :: DebugTrace -> IO () Source #
Print information about the observed function calls to stdout,
in a human-readable format.
debugJSONTrace :: DebugTrace -> ByteString Source #
Obtain information about observed functions in JSON format. The JSON format is not considered a stable part of the interface, more presented as a back door to allow exploration of alternative views.
debugViewTrace :: DebugTrace -> IO () Source #
Open a web browser showing information about observed functions.
debugSaveTrace :: FilePath -> DebugTrace -> IO () Source #
Save information about observed functions to the specified file, in HTML format.
Reexported from Hoed
class Observable a where #
A type class for observable values.
- For
Genericdatatypes it can be derived automatically. - For opaque datatypes, use
observeOpaqueor rely on the catch-all?instance. - Custom implementations can exclude one or more fields from the observation:
instance (Observable a, Observable b) => Observable (excluded, a,b) where
observe (excluded,a,b) = send "(,,)" (return (,,) excluded << a << b)
Instances
| Observable Bool | |
| Observable Char | |
| Observable Double | |
| Observable Float | |
| Observable Int | |
| Observable Integer | |
| Observable () | |
| Observable Dynamic | |
| Observable SomeException | |
| Observable a => Observable [a] | |
| Observable a => Observable (Maybe a) | |
| Observable a => Observable (IO a) | |
| (Observable a, Observable b) => Observable (a -> b) | |
| (Observable a, Observable b) => Observable (Either a b) | |
| (Observable a, Observable b) => Observable (a, b) | |
| (Ix a, Observable a, Observable b) => Observable (Array a b) | |
| (Observable a, Observable b, Observable c) => Observable (a, b, c) | |
| (Observable a, Observable b, Observable c, Observable d) => Observable (a, b, c, d) | |
| (Observable a, Observable b, Observable c, Observable d, Observable e) => Observable (a, b, c, d, e) | |
observe :: Observable a => Text -> a -> a #
Functions which you suspect of misbehaving are annotated with observe and should have a cost centre set. The name of the function, the label of the cost centre and the label given to observe need to be the same.
Consider the following function:
triple x = x + x
This function is annotated as follows:
triple y = (observe "triple" (\x -> {# SCC "triple" #} x + x)) yTo produce computation statements like:
triple 3 = 6
To observe a value its type needs to be of class Observable. We provided instances for many types already. If you have defined your own type, and want to observe a function that takes a value of this type as argument or returns a value of this type, an Observable instance can be derived as follows:
data MyType = MyNumber Int | MyName String deriving Generic instance Observable MyType
data HoedOptions :: * #
Configuration options for running Hoed
Constructors
| HoedOptions | |
Fields
| |
defaultHoedOptions :: HoedOptions #
The default is to run silent and pretty print with a width of 110 characters