Hoed-0.3.5: Lightweight algorithmic debugging.

Copyright(c) 2000 Andy Gill, (c) 2010 University of Kansas, (c) 2013-2015 Maarten Faddegon
LicenseBSD3
Maintainerhoed@maartenfaddegon.nl
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Debug.Hoed.Pure

Contents

Description

Hoed is a tracer and debugger for the programming language Haskell.

Hoed.Pure is recommended over Hoed.Stk: in contrast to Hoed.Stk you can optimize your program and do not need to enable profiling when using Hoed.Pure.

To locate a defect with Hoed.Pure you annotate suspected functions and compile as usual. Then you run your program, information about the annotated functions is collected. Finally you connect to a debugging session using a webbrowser.

Let us consider the following program, a defective implementation of a parity function with a test property.

import Test.QuickCheck

isOdd :: Int -> Bool
isOdd n = isEven (plusOne n)

isEven :: Int -> Bool
isEven n = mod2 n == 0

plusOne :: Int -> Int
plusOne n = n + 1

mod2 :: Int -> Int
mod2 n = div n 2

prop_isOdd :: Int -> Bool
prop_isOdd x = isOdd (2*x+1)

main :: IO ()
main = printO (prop_isOdd 1)

main :: IO ()
main = quickcheck prop_isOdd

Using the property-based test tool QuickCheck we find the counter example `1` for our property.

./MyProgram
*** Failed! Falsifiable (after 1 test): 1

Hoed can help us determine which function is defective. We annotate the functions isOdd, isEven, plusOne and mod2 as follows:

import Debug.Hoed.Pure

isOdd :: Int -> Bool
isOdd = observe "isOdd" isOdd'
isOdd' n = isEven (plusOne n)

isEven :: Int -> Bool
isEven = observe "isEven" isEven'
isEven' n = mod2 n == 0

plusOne :: Int -> Int
plusOne = observe "plusOne" plusOne'
plusOne' n = n + 1

mod2 :: Int -> Int
mod2 = observe "mod2" mod2'
mod2' n = div n 2

prop_isOdd :: Int -> Bool
prop_isOdd x = isOdd (2*x+1)

main :: IO ()
main = printO (prop_isOdd 1)

After running the program a computation tree is constructed and displayed in a web browser.

./MyProgram
False
Listening on http://127.0.0.1:10000/

After running the program a computation tree is constructed and displayed in a web browser. You can freely browse this tree to get a better understanding of your program. If your program misbehaves, you can judge the computation statements in the tree as right or wrong according to your intention. When enough statements are judged the debugger tells you the location of the fault in your code.

Read more about Hoed on its project homepage https://wiki.haskell.org/Hoed.

Papers on the theory behind Hoed can be obtained via http://maartenfaddegon.nl/#pub.

I am keen to hear about your experience with Hoed: where did you find it useful and where would you like to see improvement? You can send me an e-mail at hoed@maartenfaddegon.nl, or use the github issue tracker https://github.com/MaartenFaddegon/hoed/issues.

Synopsis

Basic annotations

observe :: Observable a => String -> a -> a Source

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)) y

To 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

runO :: IO a -> IO () Source

The main entry point; run some IO code, and debug inside it. After the IO action is completed, an algorithmic debugging session is started at http://localhost:10000/ to which you can connect with your webbrowser.

For example:

  main = runO $ do print (triple 3)
                   print (triple 2)

printO :: Show a => a -> IO () Source

Short for runO . print.

testO :: Show a => (a -> Bool) -> a -> IO () Source

Repeat and trace a failing testcase

Property-assisted algorithmic debugging

runOwp :: [Propositions] -> IO a -> IO () Source

Use property based judging.

testOwp :: Show a => [Propositions] -> (a -> Bool) -> a -> IO () Source

Repeat and trace a failing testcase

data PropType Source

Constructors

Specify 
PropertiesOf 

Instances

data Module Source

Constructors

Module 

Instances

class ParEq a where Source

Minimal complete definition

Nothing

Methods

(===) :: a -> a -> Maybe Bool Source

runOstore :: String -> IO a -> IO () Source

Hoed internal function that stores a serialized version of the tree on disk (assisted debugging spawns new instances of Hoed).

conAp :: Observable b => (a -> b) -> b -> a -> b Source

Build your own debugger with Hoed

runO' :: Verbosity -> IO a -> IO (Trace, TraceInfo, CompTree, EventForest) Source

Entry point giving you access to the internals of Hoed. Also see: runO.

judge :: Trace -> Propositions -> Vertex -> (CompTree -> Int) -> CompTree -> IO Judge Source

Use propositions to judge a computation statement. First tries restricted and bottom for unevaluated expressions, then unrestricted and random values for unevaluated expressions.

unjudgedCharacterCount :: CompTree -> Int Source

Approximates the complexity of a computation tree by summing the length of the unjudged computation statements (i.e not Right or Wrong) in the tree.

type CompTree = Graph Vertex () Source

The forest of computation trees. Also see the Libgraph library.

data Judge Source

Constructors

Judge Judgement

Returns a Judgement (see Libgraph library).

AlternativeTree CompTree Trace

Found counter example with simpler computation tree.

data Verbosity Source

Constructors

Verbose 
Silent 

Alternative template Haskell annotations

API to test Hoed itself

logO :: FilePath -> IO a -> IO () Source

Trace and write computation tree to file. Useful for regression testing.

logOwp :: UnevalHandler -> FilePath -> [Propositions] -> IO a -> IO () Source

As logO, but with property-based judging.

traceOnly :: IO a -> IO () Source

Only produces a trace. Useful for performance measurements.

The Observable class

newtype Observer Source

Constructors

O (forall a. Observable a => String -> a -> a) 

(<<) :: Observable a => ObserverM (a -> b) -> a -> ObserverM b infixl 9 Source

thunk :: (a -> Parent -> a) -> a -> ObserverM a Source

nothunk :: a -> ObserverM a Source

send :: String -> ObserverM a -> Parent -> a Source

observeOpaque :: String -> a -> Parent -> a Source

observeBase :: Show a => a -> Parent -> a Source

constrainBase :: Eq a => a -> a -> a Source

debugO :: IO a -> IO Trace Source

run some code and return the Trace

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic Exp 
Generic Match 
Generic Clause 
Generic Pat 
Generic Type 
Generic Dec 
Generic Name 
Generic FunDep 
Generic TyVarBndr 
Generic () 
Generic Con 
Generic Void 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic Doc 
Generic TextDetails 
Generic Style 
Generic Mode 
Generic WindowBits 
Generic ModName 
Generic PkgName 
Generic Module 
Generic OccName 
Generic NameFlavour 
Generic NameSpace 
Generic Loc 
Generic Info 
Generic ModuleInfo 
Generic Fixity 
Generic FixityDirection 
Generic Lit 
Generic Body 
Generic Guard 
Generic Stmt 
Generic Range 
Generic TySynEqn 
Generic FamFlavour 
Generic Foreign 
Generic Callconv 
Generic Safety 
Generic Pragma 
Generic Inline 
Generic RuleMatch 
Generic Phases 
Generic RuleBndr 
Generic AnnTarget 
Generic Strict 
Generic TyLit 
Generic Role 
Generic AnnLookup 
Generic Format 
Generic Method 
Generic CompressionLevel 
Generic MemoryLevel 
Generic CompressionStrategy 
Generic Judgement 
Generic AssistedMessage 
Generic CompStmt 
Generic Vertex 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Maybe a) 
Generic (Identity a) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (Graph vertex arc) 
Generic (Arc vertex arc) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (Alt k f a) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g)