quickcheck-state-machine-0.6.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@here.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

forAllCommands Source #

Arguments

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

Minimum number of commands.

-> (Commands cmd resp -> prop)

Predicate.

-> Property 

transitionMatrix :: forall cmd. CommandNames cmd => Proxy (cmd Symbolic) -> (String -> String -> Int) -> Matrix Int Source #

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

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

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

Print distribution of commands and 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 #

Parallel property combinators

forAllParallelCommands Source #

Arguments

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

Predicate.

-> Property 

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

runParallelCommandsNTimes Source #

Arguments

:: (Show (cmd Concrete), Show (resp Concrete)) 
=> (Traversable cmd, Foldable resp) 
=> (MonadCatch 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, Logic)] 

prettyParallelCommands Source #

Arguments

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

Output of runParallelCommands.

-> PropertyM m () 

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

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))) (Maybe (Matrix Int)) (model Symbolic -> cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic)) 

data Concrete a Source #

Instances
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 #

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

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Concrete a -> Expr #

listToExpr :: [Concrete a] -> Expr #

data Symbolic a Source #

Instances
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 #

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 #

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 #

ToExpr a => ToExpr (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Symbolic a -> Expr #

listToExpr :: [Symbolic a] -> Expr #

data Reference a r Source #

Instances
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 #

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 #

(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 #

(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 #

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 #

ToExpr (r a) => ToExpr (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Reference a r -> Expr #

listToExpr :: [Reference a r] -> Expr #

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.6.0-LSB9KqOf7Vm4DfY8PJnoGQ" False) (C1 (MetaCons "Reference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (r a))))

newtype Opaque a Source #

Constructors

Opaque 

Fields

Instances
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 #

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 #

ToExpr (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Opaque a -> Expr #

listToExpr :: [Opaque a] -> Expr #

data GenSym a Source #

Instances
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 #

fail :: String -> 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 #

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 #

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

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

Name of all possible commands

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

Name of this particular command

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

Name of all possible commands

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: U1 r -> String Source #

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

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: Rec1 f r -> String Source #

cmdNames :: 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 :: (f :*: g) r -> String Source #

cmdNames :: 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 :: (f :+: g) r -> String Source #

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

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: K1 i c r -> String Source #

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

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: M1 S c f r -> String Source #

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

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: M1 D c f r -> String Source #

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

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

Defined in Test.StateMachine.ConstructorName

Methods

cmdName :: M1 C c f r -> String Source #

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