quickcheck-state-machine-0.9.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.andjelkovic@strath.ac.uk>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.StateMachine

Description

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

Synopsis

Sequential property combinators

forAllCommands Source #

Arguments

:: Testable prop 
=> (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) 
=> (Traversable cmd, Foldable resp) 
=> StateMachine model cmd m resp 
-> Maybe Int

Minimum number of commands.

-> (Commands cmd resp -> prop)

Predicate.

-> Property 

existsCommands Source #

Arguments

:: forall model cmd m resp prop. (Testable prop, Foldable resp) 
=> (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) 
=> StateMachine model cmd m resp 
-> [model Symbolic -> Gen (cmd Symbolic)]

Generators.

-> (Commands cmd resp -> prop)

Predicate.

-> Property 

Generate commands from a list of generators.

runCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => StateMachine model cmd m resp -> Commands cmd resp -> PropertyM m (History cmd resp, model Concrete, Reason) Source #

runCommandsWithSetup :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => m (StateMachine model cmd m resp) -> Commands cmd resp -> PropertyM m (History cmd resp, model Concrete, Reason) Source #

prettyCommands :: (MonadIO m, CanDiff (model Concrete)) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> Property -> PropertyM m () Source #

prettyCommands' :: (MonadIO m, CanDiff (model Concrete), CanDiff [tag]) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> Commands cmd resp -> History cmd resp -> Property -> PropertyM m () Source #

Variant of prettyCommands that also prints the tags covered by each command.

checkCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property Source #

Print the percentage of each command used. The prefix check is an unfortunate remaining for backwards compatibility.

coverCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property Source #

Fail if some commands have not been executed.

commandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [(String, Int)] Source #

commandNamesInOrder :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [String] Source #

saveCommands :: (Show (cmd Symbolic), Show (resp Symbolic)) => FilePath -> Commands cmd resp -> Property -> Property Source #

runSavedCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => (Read (cmd Symbolic), Read (resp Symbolic)) => StateMachine model cmd m resp -> FilePath -> PropertyM m (Commands cmd resp, History cmd resp, model Concrete, Reason) Source #

showLabelledExamples :: (Show tag, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> IO () Source #

showLabelledExamples' Source #

Arguments

:: (Show tag, Show (model Symbolic)) 
=> (Show (cmd Symbolic), Show (resp Symbolic)) 
=> (Traversable cmd, Foldable resp) 
=> StateMachine model cmd m resp 
-> Maybe Int

Seed

-> Int

Number of tests to run to find examples

-> ([Event model cmd resp Symbolic] -> [tag]) 
-> (tag -> Bool)

Tag filter (can be const True)

-> IO () 

Show minimal examples for each of the generated tags.

noCleanup :: Monad m => model Concrete -> m () Source #

Parallel property combinators

forAllParallelCommands Source #

Arguments

:: Testable prop 
=> (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) 
=> (Traversable cmd, Foldable resp) 
=> StateMachine model cmd m resp 
-> Maybe Int 
-> (ParallelCommands cmd resp -> prop)

Predicate.

-> Property 

forAllNParallelCommands Source #

Arguments

:: Testable prop 
=> (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) 
=> (Traversable cmd, Foldable resp) 
=> StateMachine model cmd m resp 
-> Int

Number of threads

-> (NParallelCommands cmd resp -> prop)

Predicate.

-> Property 

runNParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, model Concrete, Logic)] Source #

runNParallelCommandsWithSetup :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => m (StateMachine model cmd m resp) -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, model Concrete, Logic)] Source #

runParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, model Concrete, Logic)] Source #

runParallelCommandsWithSetup :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => m (StateMachine model cmd m resp) -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, model Concrete, Logic)] Source #

runParallelCommands' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => m (StateMachine model cmd m resp) -> (cmd Concrete -> resp Concrete) -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, model Concrete, Logic)] Source #

runParallelCommandsNTimes Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> StateMachine model cmd m resp 
-> ParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

runParallelCommandsNTimesWithSetup Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> m (StateMachine model cmd m resp) 
-> ParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

runNParallelCommandsNTimes' Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> m (StateMachine model cmd m resp) 
-> (cmd Concrete -> resp Concrete) 
-> NParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

runParallelCommandsNTimes' Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> m (StateMachine model cmd m resp) 
-> (cmd Concrete -> resp Concrete) 
-> ParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

runNParallelCommandsNTimes Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> StateMachine model cmd m resp 
-> NParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

runNParallelCommandsNTimesWithSetup Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadMask m, MonadUnliftIO m) 
=> Int

How many times to execute the parallel program.

-> m (StateMachine model cmd m resp) 
-> NParallelCommands cmd resp 
-> PropertyM m [(History cmd resp, model Concrete, Logic)] 

prettyNParallelCommands Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> MonadIO m 
=> Foldable cmd 
=> NParallelCommands cmd resp 
-> [(History cmd resp, a, Logic)]

Output of runNParallelCommands.

-> PropertyM m () 

prettyParallelCommands Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> MonadIO m 
=> Foldable cmd 
=> ParallelCommands cmd resp 
-> [(History cmd resp, a, Logic)]

Output of runNParallelCommands.

-> PropertyM m () 

prettyParallelCommandsWithOpts Source #

Arguments

:: (MonadIO m, Foldable cmd) 
=> (Show (cmd Concrete), Show (resp Concrete)) 
=> ParallelCommands cmd resp 
-> Maybe GraphOptions 
-> [(History cmd resp, a, Logic)]

Output of runParallelCommands.

-> PropertyM m () 

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

prettyNParallelCommandsWithOpts Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> MonadIO m 
=> Foldable cmd 
=> NParallelCommands cmd resp 
-> Maybe GraphOptions 
-> [(History cmd resp, a, Logic)]

Output of runNParallelCommands.

-> PropertyM m () 

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

checkCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property Source #

Print the percentage of each command used. The prefix check is an unfortunate remaining for backwards compatibility.

coverCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property Source #

Fail if some commands have not been executed.

commandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> [(String, Int)] Source #

Types

data StateMachine model cmd m resp Source #

Constructors

StateMachine (forall r. model r) (forall r. (Show1 r, Ord1 r) => model r -> cmd r -> resp r -> model r) (model Symbolic -> cmd Symbolic -> Logic) (model Concrete -> cmd Concrete -> resp Concrete -> Logic) (Maybe (model Concrete -> Logic)) (model Symbolic -> Maybe (Gen (cmd Symbolic))) (model Symbolic -> cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic)) (model Concrete -> m ()) 

data Concrete a Source #

Instances

Instances details
Eq1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftEq :: (a -> b -> Bool) -> Concrete a -> Concrete b -> Bool #

Ord1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftCompare :: (a -> b -> Ordering) -> Concrete a -> Concrete b -> Ordering #

Show1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Concrete a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Concrete a] -> ShowS #

Show a => Show (Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Concrete a -> ShowS #

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

Eq a => Eq (Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Concrete a -> Concrete a -> Bool #

(/=) :: Concrete a -> Concrete a -> Bool #

Ord a => Ord (Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Concrete a -> Concrete a -> Ordering #

(<) :: Concrete a -> Concrete a -> Bool #

(<=) :: Concrete a -> Concrete a -> Bool #

(>) :: Concrete a -> Concrete a -> Bool #

(>=) :: Concrete a -> Concrete a -> Bool #

max :: Concrete a -> Concrete a -> Concrete a #

min :: Concrete a -> Concrete a -> Concrete a #

data Symbolic a Source #

Instances

Instances details
Eq1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftEq :: (a -> b -> Bool) -> Symbolic a -> Symbolic b -> Bool #

Ord1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftCompare :: (a -> b -> Ordering) -> Symbolic a -> Symbolic b -> Ordering #

Show1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Symbolic a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Symbolic a] -> ShowS #

Typeable a => Read (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Show (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Symbolic a -> ShowS #

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

Eq (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Symbolic a -> Symbolic a -> Bool #

(/=) :: Symbolic a -> Symbolic a -> Bool #

Ord (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Symbolic a -> Symbolic a -> Ordering #

(<) :: Symbolic a -> Symbolic a -> Bool #

(<=) :: Symbolic a -> Symbolic a -> Bool #

(>) :: Symbolic a -> Symbolic a -> Bool #

(>=) :: Symbolic a -> Symbolic a -> Bool #

max :: Symbolic a -> Symbolic a -> Symbolic a #

min :: Symbolic a -> Symbolic a -> Symbolic a #

Typeable a => Read (Reference a Symbolic) Source # 
Instance details

Defined in Test.StateMachine.Types.References

data Reference a r Source #

Instances

Instances details
Foldable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> Reference a p -> m Source #

Functor (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

fmap :: (forall (x :: k). p x -> q x) -> Reference a p -> Reference a q Source #

Traversable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

traverse :: Applicative f => (forall (a0 :: k). p a0 -> f (q a0)) -> Reference a p -> f (Reference a q) Source #

Generic (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Associated Types

type Rep (Reference a r) :: Type -> Type #

Methods

from :: Reference a r -> Rep (Reference a r) x #

to :: Rep (Reference a r) x -> Reference a r #

Typeable a => Read (Reference a Symbolic) Source # 
Instance details

Defined in Test.StateMachine.Types.References

(Show1 r, Show a) => Show (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Reference a r -> ShowS #

show :: Reference a r -> String #

showList :: [Reference a r] -> ShowS #

(Eq a, Eq1 r) => Eq (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Reference a r -> Reference a r -> Bool #

(/=) :: Reference a r -> Reference a r -> Bool #

(Ord a, Ord1 r) => Ord (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Reference a r -> Reference a r -> Ordering #

(<) :: Reference a r -> Reference a r -> Bool #

(<=) :: Reference a r -> Reference a r -> Bool #

(>) :: Reference a r -> Reference a r -> Bool #

(>=) :: Reference a r -> Reference a r -> Bool #

max :: Reference a r -> Reference a r -> Reference a r #

min :: Reference a r -> Reference a r -> Reference a r #

type Rep (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

type Rep (Reference a r) = D1 ('MetaData "Reference" "Test.StateMachine.Types.References" "quickcheck-state-machine-0.9.0-8zWHYIJYc77JtQ2efkvn1E-no-vendored-treediff" 'True) (C1 ('MetaCons "Reference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a))))

newtype Opaque a Source #

Constructors

Opaque 

Fields

Instances

Instances details
Show (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Opaque a -> ShowS #

show :: Opaque a -> String #

showList :: [Opaque a] -> ShowS #

Eq a => Eq (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Opaque a -> Opaque a -> Bool #

(/=) :: Opaque a -> Opaque a -> Bool #

Ord a => Ord (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Opaque a -> Opaque a -> Ordering #

(<) :: Opaque a -> Opaque a -> Bool #

(<=) :: Opaque a -> Opaque a -> Bool #

(>) :: Opaque a -> Opaque a -> Bool #

(>=) :: Opaque a -> Opaque a -> Bool #

max :: Opaque a -> Opaque a -> Opaque a #

min :: Opaque a -> Opaque a -> Opaque a #

data GenSym a Source #

Instances

Instances details
Applicative GenSym Source # 
Instance details

Defined in Test.StateMachine.Types.GenSym

Methods

pure :: a -> GenSym a #

(<*>) :: GenSym (a -> b) -> GenSym a -> GenSym b #

liftA2 :: (a -> b -> c) -> GenSym a -> GenSym b -> GenSym c #

(*>) :: GenSym a -> GenSym b -> GenSym b #

(<*) :: GenSym a -> GenSym b -> GenSym a #

Functor GenSym Source # 
Instance details

Defined in Test.StateMachine.Types.GenSym

Methods

fmap :: (a -> b) -> GenSym a -> GenSym b #

(<$) :: a -> GenSym b -> GenSym a #

Monad GenSym Source # 
Instance details

Defined in Test.StateMachine.Types.GenSym

Methods

(>>=) :: GenSym a -> (a -> GenSym b) -> GenSym b #

(>>) :: GenSym a -> GenSym b -> GenSym b #

return :: a -> GenSym a #

class CommandNames (cmd :: k -> Type) where Source #

The names of all possible commands

This is used for things like tagging, coverage checking, etc.

Minimal complete definition

Nothing

Methods

cmdName :: cmd r -> String Source #

Name of this particular command

default cmdName :: (Generic1 cmd, CommandNames (Rep1 cmd)) => cmd r -> String Source #

cmdNames :: Proxy (cmd r) -> [String] Source #

Name of all possible commands

default cmdNames :: forall r. CommandNames (Rep1 cmd) => Proxy (cmd r) -> [String] Source #

Instances

Instances details
CommandNames (U1 :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). U1 r -> String Source #

cmdNames :: forall (r :: k0). Proxy (U1 r) -> [String] Source #

CommandNames f => CommandNames (Rec1 f :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). Rec1 f r -> String Source #

cmdNames :: forall (r :: k0). Proxy (Rec1 f r) -> [String] Source #

(CommandNames f, CommandNames g) => CommandNames (f :*: g :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). (f :*: g) r -> String Source #

cmdNames :: forall (r :: k0). Proxy ((f :*: g) r) -> [String] Source #

(CommandNames f, CommandNames g) => CommandNames (f :+: g :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). (f :+: g) r -> String Source #

cmdNames :: forall (r :: k0). Proxy ((f :+: g) r) -> [String] Source #

CommandNames (K1 i c :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). K1 i c r -> String Source #

cmdNames :: forall (r :: k0). Proxy (K1 i c r) -> [String] Source #

Constructor c => CommandNames (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). M1 C c f r -> String Source #

cmdNames :: forall (r :: k0). Proxy (M1 C c f r) -> [String] Source #

CommandNames f => CommandNames (M1 D c f :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). M1 D c f r -> String Source #

cmdNames :: forall (r :: k0). Proxy (M1 D c f r) -> [String] Source #

CommandNames f => CommandNames (M1 S c f :: k -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: forall (r :: k0). M1 S c f r -> String Source #

cmdNames :: forall (r :: k0). Proxy (M1 S c f r) -> [String] Source #

Diffing class

class CanDiff x where Source #

Associated Types

type AnExpr x Source #

Expressions that will be diffed

type ADiff x Source #

What will the diff of two AnExprs result in

Methods

toDiff :: x -> AnExpr x Source #

Extract the expression from the data

exprDiff :: Proxy x -> AnExpr x -> AnExpr x -> ADiff x Source #

Diff two expressions

diffToDocCompact :: Proxy x -> ADiff x -> Doc Source #

Output a diff in compact form

diffToDoc :: Proxy x -> ADiff x -> Doc Source #

Output a diff

exprToDoc :: Proxy x -> AnExpr x -> Doc Source #

Output an expression