| Copyright | (c) 2000 Andy Gill (c) 2010 University of Kansas (c) 2013-2018 Maarten Faddegon | 
|---|---|
| License | BSD3 | 
| Maintainer | hoed@maartenfaddegon.nl | 
| Stability | experimental | 
| Portability | POSIX | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Debug.Hoed
Contents
Description
Hoed is a tracer and debugger for the programming language Haskell.
To locate a defect with Hoed 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 console.
With Hoed you can list and search observed functions applied to argument values and the result values. Hoed also provides algorithmic debugging. An algorithmic debugger finds defects in programs by systematic search. The programmer directs the search by answering a series of yes/no questions about the correctness of specific function applications and their results. Hoed also allows the use of (QuickCheck-style) properties to answer automatically some of the questions arising during algorithmic debugging, and to replace others by simpler questions.
Example usage
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 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 the algorithmic debugger is launched in the console.
False
=== program terminated ===
Please wait while the computation tree is constructed...
=== Statistics ===
28 events
4 computation statements
4 nodes + 1 virtual root node in the computation tree
4 edges in computation tree
computation tree has a branch factor of 1.3333333333333333 (i.e the average number of children of non-leaf nodes)
=== Debug Session ===
hdb> adb
======================================================================= [0-0/4]
isOdd 3  = False
? 
right  Judge computation statements right
        according to the intended behaviour/specification of the function.
wrong  Judge computation statements wrong
        according to the intended behaviour/specification of the function.
======================================================================= [0-0/4]
isOdd 3  = False
? wrong
======================================================================= [1-0/4]
isEven 4  = False
? wrong
======================================================================= [2-0/4]
mod2 4  = 2
? wrong
======================================================================= [3-0/4]
Fault located! In:
mod2 4  = 2
hdb>
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.
- observe :: Observable a => Text -> a -> a
- runO :: IO a -> IO ()
- printO :: Show a => a -> IO ()
- testO :: Show a => (a -> Bool) -> a -> IO ()
- runOwith :: HoedOptions -> IO a -> IO ()
- data HoedOptions = HoedOptions {- verbose :: Verbosity
- prettyWidth :: Int
 
- defaultHoedOptions :: HoedOptions
- runOwp :: [Propositions] -> IO a -> IO ()
- printOwp :: Show a => [Propositions] -> a -> IO ()
- testOwp :: Show a => [Propositions] -> (a -> Bool) -> a -> IO ()
- data Propositions = Propositions {- propositions :: [Proposition]
- propType :: PropType
- funName :: String
- extraModules :: [Module]
 
- data PropType
- data Proposition = Proposition {- propositionType :: PropositionType
- propModule :: Module
- propName :: String
- signature :: [Signature]
- maxSize :: Maybe Int
- testgen :: TestGen
 
- mkProposition :: Module -> String -> Proposition
- ofType :: Proposition -> PropositionType -> Proposition
- withSignature :: Proposition -> [Signature] -> Proposition
- sizeHint :: Proposition -> Int -> Proposition
- withTestGen :: Proposition -> TestGen -> Proposition
- data TestGen
- data PropositionType
- data Module = Module {- moduleName :: String
- searchPath :: String
 
- data Signature
- class ParEq a where
- (===) :: ParEq a => a -> a -> Bool
- runOstore :: String -> IO a -> IO ()
- conAp :: Observable b => (a -> b) -> b -> a -> b
- data HoedAnalysis = HoedAnalysis {}
- runO' :: HoedOptions -> IO a -> IO HoedAnalysis
- judge :: Trace -> Propositions -> Vertex -> (CompTree -> Int) -> CompTree -> IO Judge
- unjudgedCharacterCount :: CompTree -> Int
- type CompTree = Graph Vertex ()
- data Vertex- = RootVertex
- | Vertex { }
 
- data CompStmt = CompStmt {- stmtLabel :: !Text
- stmtIdentifier :: !UID
- stmtDetails :: !StmtDetails
 
- data Judge
- data Verbosity
- logO :: FilePath -> IO a -> IO ()
- logOwp :: UnevalHandler -> FilePath -> [Propositions] -> IO a -> IO ()
- traceOnly :: IO a -> IO ()
- data UnevalHandler- = RestrictedBottom
- | Bottom
- | Forall
- | FromList [String]
 
- class Observable a where
- (<<) :: Observable a => ObserverM (a -> b) -> a -> ObserverM b
- thunk :: (a -> Parent -> a) -> a -> ObserverM a
- send :: Text -> ObserverM a -> Parent -> a
- observeOpaque :: Text -> a -> Parent -> a
- observeBase :: Show a => a -> Parent -> a
- constrainBase :: (Show a, Eq a) => a -> a -> a
- debugO :: IO a -> IO Trace
- data CDS
- class Generic a
Basic annotations
observe :: Observable a => Text -> 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)) 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
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)
data HoedOptions Source #
Configuration options for running Hoed
Constructors
| HoedOptions | |
| Fields 
 | |
defaultHoedOptions :: HoedOptions Source #
The default is to run silent and pretty print with a width of 110 characters
Property-assisted algorithmic debugging
testOwp :: Show a => [Propositions] -> (a -> Bool) -> a -> IO () Source #
Repeat and trace a failing testcase
data Propositions Source #
Constructors
| Propositions | |
| Fields 
 | |
data Proposition Source #
Constructors
| Proposition | |
| Fields 
 | |
Instances
mkProposition :: Module -> String -> Proposition Source #
ofType :: Proposition -> PropositionType -> Proposition Source #
withSignature :: Proposition -> [Signature] -> Proposition Source #
sizeHint :: Proposition -> Int -> Proposition Source #
withTestGen :: Proposition -> TestGen -> Proposition Source #
Constructors
| TestGenQuickCheck | |
| TestGenLegacyQuickCheck | 
data PropositionType Source #
Instances
Constructors
| Module | |
| Fields 
 | |
Constructors
| Argument Int | |
| SubjectFunction | |
| Random | 
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
data HoedAnalysis Source #
Constructors
| HoedAnalysis | |
| Fields 
 | |
runO' :: HoedOptions -> IO a -> IO HoedAnalysis 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 finally with randomly generated 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.
Constructors
| RootVertex | |
| Vertex | |
| Fields 
 | |
Constructors
| CompStmt | |
| Fields 
 | |
Constructors
| Judge Judgement | Returns a Judgement (see Libgraph library). | 
| AlternativeTree CompTree Trace | Found counter example with simpler computation tree. | 
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.
The Observable class
class Observable a where Source #
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)
Methods
observer :: a -> Parent -> a Source #
observer :: (Generic a, GObservable (Rep a)) => a -> Parent -> a Source #
constrain :: a -> a -> a Source #
constrain :: (Generic a, GConstrain (Rep a)) => a -> a -> a Source #
Instances
| Observable Bool Source # | |
| Observable Char Source # | |
| Observable Double Source # | |
| Observable Float Source # | |
| Observable Int Source # | |
| Observable Integer Source # | |
| Observable () Source # | |
| Observable Dynamic Source # | |
| Observable SomeException Source # | |
| Observable a => Observable [a] Source # | |
| Observable a => Observable (Maybe a) Source # | |
| Observable a => Observable (IO a) Source # | |
| (Observable a, Observable b) => Observable (a -> b) Source # | |
| (Observable a, Observable b) => Observable (Either a b) Source # | |
| (Observable a, Observable b) => Observable (a, b) Source # | |
| (Ix a, Observable a, Observable b) => Observable (Array a b) Source # | |
| (Observable a, Observable b, Observable c) => Observable (a, b, c) Source # | |
| (Observable a, Observable b, Observable c, Observable d) => Observable (a, b, c, d) Source # | |
| (Observable a, Observable b, Observable c, Observable d, Observable e) => Observable (a, b, c, d, e) Source # | |
observeOpaque :: Text -> a -> Parent -> a Source #
observeBase :: Show a => a -> Parent -> a Source #
constrainBase :: (Show a, Eq a) => a -> a -> a Source #
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances
Orphan instances
| Observable a Source # | A catch-all instance for non observable types that produces the opaque observation  |