Copyright | (C) 2017 ATS Advanced Telematic Systems GmbH |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Stevan Andjelkovic <stevan@advancedtelematic.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
The main module for state machine based testing, it contains combinators that help you build sequential and parallel properties.
Synopsis
- forAllCommands :: Testable prop => (Show (cmd Symbolic), Show (model Symbolic)) => (Generic1 cmd, GConName1 (Rep1 cmd)) => (Foldable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> (Commands cmd -> prop) -> Property
- transitionMatrix :: forall cmd. GConName1 (Rep1 cmd) => Proxy (cmd Symbolic) -> (String -> String -> Int) -> Matrix Int
- modelCheck :: forall model cmd resp m. Monad m => StateMachine model cmd m resp -> Commands cmd -> PropertyM m Reason
- runCommands :: (Traversable cmd, Foldable resp) => (MonadCatch m, MonadBaseControl IO m) => StateMachine model cmd m resp -> Commands cmd -> PropertyM m (History cmd resp, model Concrete, Reason)
- prettyCommands :: (MonadIO m, ToExpr (model Concrete)) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> Property -> PropertyM m ()
- checkCommandNames :: forall cmd. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> Property -> Property
- commandNames :: forall cmd. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> [(String, Int)]
- commandNamesInOrder :: forall cmd. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> [String]
- forAllParallelCommands :: Testable prop => (Show (cmd Symbolic), Show (model Symbolic)) => (Generic1 cmd, GConName1 (Rep1 cmd)) => (Foldable cmd, Foldable resp) => StateMachine model cmd m resp -> (ParallelCommands cmd -> prop) -> Property
- runParallelCommands :: (Traversable cmd, Foldable resp) => (MonadCatch m, MonadBaseControl IO m) => StateMachine model cmd m resp -> ParallelCommands cmd -> PropertyM m [(History cmd resp, Bool)]
- runParallelCommandsNTimes :: (Traversable cmd, Foldable resp) => (MonadCatch m, MonadBaseControl IO m) => Int -> StateMachine model cmd m resp -> ParallelCommands cmd -> PropertyM m [(History cmd resp, Bool)]
- prettyParallelCommands :: (MonadIO m, Foldable cmd) => (Show (cmd Concrete), Show (resp Concrete)) => ParallelCommands cmd -> [(History cmd resp, Bool)] -> PropertyM m ()
- data StateMachine model cmd m resp = 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 Symbolic -> cmd Symbolic -> resp Symbolic -> Logic)) (Maybe (model Concrete -> Logic)) (model Symbolic -> Gen (cmd Symbolic)) (Maybe (Matrix Int)) (cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (m Property -> IO Property) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic))
- data Concrete a
- data Symbolic a
- data Reference a r
- concrete :: Reference a Concrete -> a
- reference :: Typeable a => a -> Reference a Concrete
- newtype Opaque a = Opaque {
- unOpaque :: a
- opaque :: Reference (Opaque a) Concrete -> a
- data Reason
- data GenSym a
- genSym :: Typeable a => GenSym (Reference a Symbolic)
- module Test.StateMachine.Logic
Sequential property combinators
transitionMatrix :: forall cmd. GConName1 (Rep1 cmd) => Proxy (cmd Symbolic) -> (String -> String -> Int) -> Matrix Int Source #
modelCheck :: forall model cmd resp m. Monad m => StateMachine model cmd m resp -> Commands cmd -> PropertyM m Reason Source #
runCommands :: (Traversable cmd, Foldable resp) => (MonadCatch m, MonadBaseControl IO m) => StateMachine model cmd m resp -> Commands cmd -> 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. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> Property -> Property Source #
Print distribution of commands and fail if some commands have not been executed.
commandNames :: forall cmd. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> [(String, Int)] Source #
commandNamesInOrder :: forall cmd. (Generic1 cmd, GConName1 (Rep1 cmd)) => Commands cmd -> [String] Source #
Parallel property combinators
runParallelCommands :: (Traversable cmd, Foldable resp) => (MonadCatch m, MonadBaseControl IO m) => StateMachine model cmd m resp -> ParallelCommands cmd -> PropertyM m [(History cmd resp, Bool)] Source #
runParallelCommandsNTimes Source #
:: (Traversable cmd, Foldable resp) | |
=> (MonadCatch m, MonadBaseControl IO m) | |
=> Int | How many times to execute the parallel program. |
-> StateMachine model cmd m resp | |
-> ParallelCommands cmd | |
-> PropertyM m [(History cmd resp, Bool)] |
prettyParallelCommands Source #
:: (MonadIO m, Foldable cmd) | |
=> (Show (cmd Concrete), Show (resp Concrete)) | |
=> ParallelCommands cmd | |
-> [(History cmd resp, Bool)] | Output of |
-> 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 #
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 Symbolic -> cmd Symbolic -> resp Symbolic -> Logic)) (Maybe (model Concrete -> Logic)) (model Symbolic -> Gen (cmd Symbolic)) (Maybe (Matrix Int)) (cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (m Property -> IO Property) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic)) |
Instances
Eq1 Symbolic Source # | |
Ord1 Symbolic Source # | |
Defined in Test.StateMachine.Types.References | |
Show1 Symbolic Source # | |
Eq (Symbolic a) Source # | |
Ord (Symbolic a) Source # | |
Defined in Test.StateMachine.Types.References | |
Show (Symbolic a) Source # | |
ToExpr a => ToExpr (Symbolic a) Source # | |
Defined in Test.StateMachine.Types.References |
Instances
Traversable (Reference a :: (* -> *) -> *) Source # | |
Defined in Test.StateMachine.Types.References | |
Foldable (Reference a :: (* -> *) -> *) Source # | |
Functor (Reference a :: (* -> *) -> *) Source # | |
(Eq a, Eq1 r) => Eq (Reference a r) Source # | |
(Ord a, Ord1 r) => Ord (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References 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 # | |
(Show1 r, Show a) => Show (Reference a r) Source # | |
Generic (Reference a r) Source # | |
ToExpr (r a) => ToExpr (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References | |
GConName1 (Reference a :: (* -> *) -> *) Source # | |
type Rep (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References |
module Test.StateMachine.Logic