Copyright | (C) 2017 ATS Advanced Telematic Systems GmbH |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Stevan Andjelkovic <stevan.andjelkovic@strath.ac.uk> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
This module contains helpers for generating, shrinking, and checking sequential programs.
Synopsis
- forAllCommands :: Testable prop => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> (Commands cmd resp -> prop) -> Property
- existsCommands :: 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)] -> (Commands cmd resp -> prop) -> Property
- generateCommands :: (Foldable resp, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => StateMachine model cmd m resp -> Maybe Int -> Gen (Commands cmd resp)
- generateCommandsState :: forall model cmd m resp. Foldable resp => (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) => StateMachine model cmd m resp -> Counter -> Maybe Int -> StateT (model Symbolic) Gen (Commands cmd resp)
- deadlockError :: (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) => model Symbolic -> [Command cmd resp] -> String -> b
- getUsedVars :: Foldable f => f Symbolic -> [Var]
- shrinkCommands :: forall model cmd m resp. (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Commands cmd resp -> [Commands cmd resp]
- shrinkAndValidate :: forall model cmd m resp. (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> ShouldShrink -> ValidateEnv model -> Commands cmd resp -> [(ValidateEnv model, Commands cmd resp)]
- data ValidateEnv model = ValidateEnv {}
- data ShouldShrink
- initValidateEnv :: model Symbolic -> ValidateEnv model
- 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)
- runCommands' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => StateMachine model cmd m resp -> Commands cmd resp -> m (History cmd resp, model Concrete, Reason)
- getChanContents :: MonadIO m => TChan a -> m [a]
- data Check
- executeCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadCatch m, MonadIO m) => StateMachine model cmd m resp -> TChan (Pid, HistoryEvent cmd resp) -> Pid -> Check -> Commands cmd resp -> StateT (Environment, model Symbolic, Counter, model Concrete) m Reason
- prettyPrintHistory :: forall model cmd m resp. ToExpr (model Concrete) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> IO ()
- prettyPrintHistory' :: forall model cmd m resp tag. ToExpr (model Concrete) => (Show (cmd Concrete), Show (resp Concrete), ToExpr tag) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> Commands cmd resp -> History cmd resp -> IO ()
- prettyCommands :: (MonadIO m, ToExpr (model Concrete)) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> Property -> PropertyM m ()
- prettyCommands' :: (MonadIO m, ToExpr (model Concrete), ToExpr 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 ()
- saveCommands :: (Show (cmd Symbolic), Show (resp Symbolic)) => FilePath -> Commands cmd resp -> Property -> Property
- 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)
- commandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [(String, Int)]
- commandNamesInOrder :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [String]
- coverCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property
- checkCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property
- 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 ()
- showLabelledExamples' :: (Show tag, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> Int -> ([Event model cmd resp Symbolic] -> [tag]) -> (tag -> Bool) -> IO ()
Documentation
:: (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.
deadlockError :: (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) => model Symbolic -> [Command cmd resp] -> String -> b Source #
shrinkCommands :: forall model cmd m resp. (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Commands cmd resp -> [Commands cmd resp] Source #
Shrink commands in a pre-condition and scope respecting way.
shrinkAndValidate :: forall model cmd m resp. (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> ShouldShrink -> ValidateEnv model -> Commands cmd resp -> [(ValidateEnv model, Commands cmd resp)] Source #
Validate list of commands, optionally shrinking one of the commands
The input to this function is a list of commands (Commands
), for example
[A, B, C, D, E, F, G, H]
The result is a list of Commands
, i.e. a list of lists. The
outermost list is used for all the shrinking possibilities. For example,
let's assume we haven't shrunk something yet, and therefore need to shrink
one of the commands. Let's further assume that only commands B and E can be
shrunk, to B1, B2 and E1, E2, E3 respectively. Then the result will look
something like
[ -- outermost list recording all the shrink possibilities [A', B1', C', D', E' , F', G', H'] -- B shrunk to B1 , [A', B2', C', D', E' , F', G', H'] -- B shrunk to B2 , [A', B' , C', D', E1', F', G', H'] -- E shrunk to E1 , [A', B' , C', D', E2', F', G', H'] -- E shrunk to E2 , [A', B' , C', D', E3', F', G', H'] -- E shrunk to E3 ]
where one of the commands has been shrunk and all commands have been validated and renumbered (references updated). So, in this example, the result will contain at most 5 lists; it may contain fewer, since some of these lists may not be valid.
If we _did_ already shrink something, then no commands will be shrunk, and the resulting list will either be empty (if the list of commands was invalid) or contain a single element with the validated and renumbered commands.
data ValidateEnv model Source #
Environment required during shrinkAndValidate
ValidateEnv | |
|
initValidateEnv :: model Symbolic -> ValidateEnv model Source #
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 #
runCommands' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => StateMachine model cmd m resp -> Commands cmd resp -> m (History cmd resp, model Concrete, Reason) Source #
getChanContents :: MonadIO m => TChan a -> m [a] Source #
executeCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadCatch m, MonadIO m) => StateMachine model cmd m resp -> TChan (Pid, HistoryEvent cmd resp) -> Pid -> Check -> Commands cmd resp -> StateT (Environment, model Symbolic, Counter, model Concrete) m Reason Source #
prettyPrintHistory :: forall model cmd m resp. ToExpr (model Concrete) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> IO () Source #
prettyPrintHistory' :: forall model cmd m resp tag. ToExpr (model Concrete) => (Show (cmd Concrete), Show (resp Concrete), ToExpr tag) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> Commands cmd resp -> History cmd resp -> IO () 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 #
prettyCommands' :: (MonadIO m, ToExpr (model Concrete), ToExpr 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 tag
s covered by each
command.
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 #
commandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [(String, Int)] Source #
commandNamesInOrder :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [String] Source #
coverCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property Source #
Fail if some commands have not been executed.
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.
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 #
:: (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 |
-> IO () |
Show minimal examples for each of the generated tags.