quickcheck-state-machine-0.3.0: Test monadic programs using state machine based models

Copyright(C) 2017 ATS Advanced Telematic Systems GmbH
LicenseBSD-style (see the file LICENSE)
MaintainerStevan Andjelkovic <stevan@advancedtelematic.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Test.StateMachine

Contents

Description

The main module for state machine based testing, it contains combinators that help you build sequential and parallel properties.

Synopsis

Sequential property combinators

data Program act Source #

A (sequential) program is an abstract datatype representing a list of actions.

The idea is that the user shows how to generate, shrink, execute and modelcheck individual actions, and then the below combinators lift those things to whole programs.

Instances

Eq (Internal act) => Eq (Program act) Source # 

Methods

(==) :: Program act -> Program act -> Bool #

(/=) :: Program act -> Program act -> Bool #

Read (Untyped act) => Read (Program act) Source # 
Show (Untyped act) => Show (Program act) Source # 

Methods

showsPrec :: Int -> Program act -> ShowS #

show :: Program act -> String #

showList :: [Program act] -> ShowS #

Monoid (Program act) Source # 

Methods

mempty :: Program act #

mappend :: Program act -> Program act -> Program act #

mconcat :: [Program act] -> Program act #

programLength :: Program act -> Int Source #

Returns the number of actions in a program.

forAllProgram Source #

Arguments

:: HFoldable act 
=> Generator model act 
-> Shrinker act 
-> Precondition model act 
-> Transition' model act err 
-> InitialModel model 
-> (Program act -> Property)

Predicate that should hold for all programs.

-> Property 

This function is like a forAllShrink for sequential programs.

monadicSequential Source #

Arguments

:: Monad m 
=> HFoldable act 
=> Testable a 
=> StateMachine' model act m err 
-> (Program act -> PropertyM m a)

Predicate that should hold for all programs.

-> Property 

Wrapper around forAllProgram using the StateMachine specification to generate and shrink sequential programs.

runProgram Source #

Arguments

:: Monad m 
=> Show1 (act Symbolic) 
=> Show err 
=> Typeable err 
=> HTraversable act 
=> StateMachine' model act m err 
-> Program act 
-> PropertyM m (History act err, model Concrete, Reason) 

Testable property of sequential programs derived from a StateMachine specification.

prettyProgram :: MonadIO m => Show (model Concrete) => Show err => StateMachine' model act m err -> History act err -> Property -> PropertyM m () Source #

Takes the output of running a program and pretty prints a counterexample if the run failed.

actionNames :: forall act. Constructors act => Program act -> [(Constructor, Int)] Source #

Returns the frequency of actions in a program.

checkActionNames :: Constructors act => Program act -> Property -> Property Source #

Print distribution of actions and fail if some actions have not been executed.

Parallel property combinators

data History act err Source #

A history is a trace of a program execution.

Instances

Monoid (History act err) Source # 

Methods

mempty :: History act err #

mappend :: History act err -> History act err -> History act err #

mconcat :: [History act err] -> History act err #

monadicParallel Source #

Arguments

:: MonadBaseControl IO m 
=> Eq (Untyped act) 
=> Show1 (act Symbolic) 
=> HFoldable act 
=> StateMachine' model act m err 
-> (ParallelProgram act -> PropertyM m ())

Predicate that should hold for all parallel programs.

-> Property 

Wrapper around 'forAllParallelProgram using the StateMachine specification to generate and shrink parallel programs.

runParallelProgram Source #

Arguments

:: MonadBaseControl IO m 
=> Show1 (act Symbolic) 
=> HTraversable act 
=> StateMachine' model act m err 
-> ParallelProgram act 
-> PropertyM m [(History act err, Property)] 

Testable property of parallel programs derived from a StateMachine specification.

runParallelProgram' Source #

Arguments

:: MonadBaseControl IO m 
=> Show1 (act Symbolic) 
=> HTraversable act 
=> Int

How many times to execute the parallel program.

-> StateMachine' model act m err 
-> ParallelProgram act 
-> PropertyM m [(History act err, Property)] 

prettyParallelProgram Source #

Arguments

:: MonadIO m 
=> HFoldable act 
=> Show (Untyped act) 
=> ParallelProgram act 
-> [(History act err, Property)]

Output of 'runParallelProgram.

-> PropertyM m () 

Takes the output of a parallel program runs and pretty prints a counter example if any of the runs fail.

With counterexamples

forAllProgramC Source #

Arguments

:: HFoldable act 
=> Generator model act 
-> Shrinker act 
-> Precondition model act 
-> Transition' model act err 
-> InitialModel model 
-> (Program act -> PropertyOf a)

Predicate that should hold for all programs.

-> PropertyOf (Program act :&: a) 

Variant of forAllProgram which returns the generated and shrunk program if the property fails.

monadicSequentialC Source #

Arguments

:: Monad m 
=> HFoldable act 
=> Testable a 
=> StateMachine' model act m err 
-> (Program act -> PropertyM m a)

Predicate that should hold for all programs.

-> PropertyOf (Program act) 

Variant of monadicSequential with counterexamples.

monadicParallelC Source #

Arguments

:: MonadBaseControl IO m 
=> Eq (Untyped act) 
=> Show1 (act Symbolic) 
=> HFoldable act 
=> StateMachine' model act m err 
-> (ParallelProgram act -> PropertyM m ())

Predicate that should hold for all parallel programs.

-> PropertyOf (ParallelProgram act) 

Variant of monadicParallel with counterexamples.

Types

Reexport

quickCheck :: Testable prop => prop -> IO () #

Tests a property and prints the results to stdout.

By default up to 100 tests are performed, which may not be enough to find all bugs. To run more tests, use withMaxSuccess.