Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- newtype Var a v = Var (v a)
- concrete :: Var a Concrete -> a
- opaque :: Var (Opaque a) Concrete -> a
- newtype Concrete a where
- data Symbolic a where
- newtype Name = Name Int
- newtype Environment = Environment {}
- data EnvironmentError
- emptyEnvironment :: Environment
- insertConcrete :: Symbolic a -> Concrete a -> Environment -> Environment
- reifyDynamic :: forall a. Typeable a => Dynamic -> Either EnvironmentError (Concrete a)
- reifyEnvironment :: Environment -> forall a. Symbolic a -> Either EnvironmentError (Concrete a)
- reify :: HTraversable t => Environment -> t Symbolic -> Either EnvironmentError (t Concrete)
- data Command gen m (state :: (* -> *) -> *) = (HTraversable input, Show (input Symbolic), Show output, Typeable output) => Command {
- commandGen :: state Symbolic -> Maybe (gen (input Symbolic))
- commandExecute :: input Concrete -> m output
- commandCallbacks :: [Callback input output state]
- data Callback input output state
- commandGenOK :: Command gen m state -> state Symbolic -> Bool
- data Action m (state :: (* -> *) -> *) = (HTraversable input, Show (input Symbolic), Show output) => Action {
- actionInput :: input Symbolic
- actionOutput :: Symbolic output
- actionExecute :: input Concrete -> m output
- actionRequire :: state Symbolic -> input Symbolic -> Bool
- actionUpdate :: forall v. Ord1 v => state v -> input v -> Var output v -> state v
- actionEnsure :: state Concrete -> state Concrete -> input Concrete -> output -> Test ()
- data Sequential m state = Sequential {
- sequentialActions :: [Action m state]
- data Parallel m state = Parallel {
- parallelPrefix :: [Action m state]
- parallelBranch1 :: [Action m state]
- parallelBranch2 :: [Action m state]
- takeVariables :: forall t. HTraversable t => t Symbolic -> Map Name TypeRep
- variablesOK :: HTraversable t => t Symbolic -> Map Name TypeRep -> Bool
- dropInvalid :: [Action m state] -> State (Context state) [Action m state]
- action :: (MonadGen gen, MonadTest m) => [Command gen m state] -> GenT (StateT (Context state) (GenBase gen)) (Action m state)
- sequential :: (MonadGen gen, MonadTest m) => Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Sequential m state)
- parallel :: (MonadGen gen, MonadTest m) => Range Int -> Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Parallel m state)
- executeSequential :: (MonadTest m, MonadCatch m, HasCallStack) => (forall v. state v) -> Sequential m state -> m ()
- executeParallel :: (MonadTest m, MonadCatch m, MonadBaseControl IO m, HasCallStack) => (forall v. state v) -> Parallel m state -> m ()
Variables
Variables are the potential or actual result of executing an action. They
are parameterised by either Symbolic
or Concrete
depending on the
phase of the test.
Symbolic
variables are the potential results of actions. These are used
when generating the sequence of actions to execute. They allow actions
which occur later in the sequence to make use of the result of an action
which came earlier in the sequence.
Concrete
variables are the actual results of actions. These are used
during test execution. They provide access to the actual runtime value of
a variable.
The state update Callback
for a command needs to be polymorphic in the
type of variable because it is used in both the generation and the
execution phase.
The order of arguments makes Var
HTraverable
, which is how Symbolic
values are turned into Concrete
ones.
Var (v a) |
newtype Concrete a where Source #
Concrete values: At test-execution time, Symbolic
values from generation
are replaced with Concrete
values from performing actions. This type
gives us something of the same kind as Symbolic
to pass as a type
argument to Var
.
Instances
Functor Concrete Source # | |
Foldable Concrete Source # | |
Defined in Hedgehog.Internal.State fold :: Monoid m => Concrete m -> m # foldMap :: Monoid m => (a -> m) -> Concrete a -> m # foldr :: (a -> b -> b) -> b -> Concrete a -> b # foldr' :: (a -> b -> b) -> b -> Concrete a -> b # foldl :: (b -> a -> b) -> b -> Concrete a -> b # foldl' :: (b -> a -> b) -> b -> Concrete a -> b # foldr1 :: (a -> a -> a) -> Concrete a -> a # foldl1 :: (a -> a -> a) -> Concrete a -> a # elem :: Eq a => a -> Concrete a -> Bool # maximum :: Ord a => Concrete a -> a # minimum :: Ord a => Concrete a -> a # | |
Traversable Concrete Source # | |
Eq1 Concrete Source # | |
Ord1 Concrete Source # | |
Defined in Hedgehog.Internal.State | |
Show1 Concrete Source # | |
Eq a => Eq (Concrete a) Source # | |
Ord a => Ord (Concrete a) Source # | |
Show a => Show (Concrete a) Source # | |
data Symbolic a where Source #
Symbolic values: Because hedgehog generates actions in a separate phase before execution, you will sometimes need to refer to the result of a previous action in a generator without knowing the value of the result (e.g., to get the ID of a previously-created user).
Symmbolic variables provide a token to stand in for the actual variables at
generation time (and in 'Require'/'Update' callbacks). At execution time,
real values are available, so your execute actions work on Concrete
variables.
Instances
Eq1 Symbolic Source # | |
Ord1 Symbolic Source # | |
Defined in Hedgehog.Internal.State | |
Show1 Symbolic Source # | |
Eq (Symbolic a) Source # | |
Ord (Symbolic a) Source # | |
Show (Symbolic a) Source # | |
Symbolic variable names.
Environment
newtype Environment Source #
A mapping of symbolic values to concrete values.
Instances
Show Environment Source # | |
Defined in Hedgehog.Internal.State showsPrec :: Int -> Environment -> ShowS # show :: Environment -> String # showList :: [Environment] -> ShowS # |
data EnvironmentError Source #
Environment errors.
Instances
Eq EnvironmentError Source # | |
Defined in Hedgehog.Internal.State (==) :: EnvironmentError -> EnvironmentError -> Bool # (/=) :: EnvironmentError -> EnvironmentError -> Bool # | |
Ord EnvironmentError Source # | |
Defined in Hedgehog.Internal.State compare :: EnvironmentError -> EnvironmentError -> Ordering # (<) :: EnvironmentError -> EnvironmentError -> Bool # (<=) :: EnvironmentError -> EnvironmentError -> Bool # (>) :: EnvironmentError -> EnvironmentError -> Bool # (>=) :: EnvironmentError -> EnvironmentError -> Bool # max :: EnvironmentError -> EnvironmentError -> EnvironmentError # min :: EnvironmentError -> EnvironmentError -> EnvironmentError # | |
Show EnvironmentError Source # | |
Defined in Hedgehog.Internal.State showsPrec :: Int -> EnvironmentError -> ShowS # show :: EnvironmentError -> String # showList :: [EnvironmentError] -> ShowS # |
emptyEnvironment :: Environment Source #
Create an empty environment.
insertConcrete :: Symbolic a -> Concrete a -> Environment -> Environment Source #
Insert a symbolic / concrete pairing in to the environment.
reifyDynamic :: forall a. Typeable a => Dynamic -> Either EnvironmentError (Concrete a) Source #
Cast a Dynamic
in to a concrete value.
reifyEnvironment :: Environment -> forall a. Symbolic a -> Either EnvironmentError (Concrete a) Source #
Turns an environment in to a function for looking up a concrete value from a symbolic one.
reify :: HTraversable t => Environment -> t Symbolic -> Either EnvironmentError (t Concrete) Source #
Convert a symbolic structure to a concrete one, using the provided environment.
Commands
data Command gen m (state :: (* -> *) -> *) Source #
The specification for the expected behaviour of an
Action
. These are used to generate sequences of actions to test.
This is the main type you will use when writing state machine
tests. gen
is usually an instance of MonadGen
, and m
is usually
an instance of MonadTest
. These constraints appear when you pass
your Command
list to sequential
or parallel
.
(HTraversable input, Show (input Symbolic), Show output, Typeable output) => Command | |
|
data Callback input output state Source #
Optional command configuration.
Require (state Symbolic -> input Symbolic -> Bool) | A pre-condition for a command that must be verified before the command can be executed. This is mainly used during shrinking to ensure that it is still OK to run a command despite the fact that some previously executed commands may have been removed from the sequence. |
Update (forall v. Ord1 v => state v -> input v -> Var output v -> state v) | Updates the model state, given the input and output of the command. Note
that this function is polymorphic in the type of values. This is because
it must work over |
Ensure (state Concrete -> state Concrete -> input Concrete -> output -> Test ()) | A post-condition for a command that must be verified for the command to be considered a success. This callback receives the state prior to execution as the first argument, and the state after execution as the second argument. |
commandGenOK :: Command gen m state -> state Symbolic -> Bool Source #
Checks that input for a command can be executed in the given state.
Actions
data Action m (state :: (* -> *) -> *) Source #
An instantiation of a Command
which can be executed, and its effect
evaluated.
(HTraversable input, Show (input Symbolic), Show output) => Action | |
|
data Sequential m state Source #
A sequence of actions to execute.
Sequential | |
|
Instances
Show (Sequential m state) Source # | |
Defined in Hedgehog.Internal.State showsPrec :: Int -> Sequential m state -> ShowS # show :: Sequential m state -> String # showList :: [Sequential m state] -> ShowS # |
data Parallel m state Source #
A sequential prefix of actions to execute, with two branches to execute in parallel.
Parallel | |
|
takeVariables :: forall t. HTraversable t => t Symbolic -> Map Name TypeRep Source #
Collects all the symbolic values in a data structure and produces a set of all the variables they refer to.
variablesOK :: HTraversable t => t Symbolic -> Map Name TypeRep -> Bool Source #
Checks that the symbolic values in the data structure refer only to the variables in the provided set, and that they are of the correct type.
dropInvalid :: [Action m state] -> State (Context state) [Action m state] Source #
Drops invalid actions from the sequence.
action :: (MonadGen gen, MonadTest m) => [Command gen m state] -> GenT (StateT (Context state) (GenBase gen)) (Action m state) Source #
Generates a single action from a set of possible commands.
sequential :: (MonadGen gen, MonadTest m) => Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Sequential m state) Source #
Generates a sequence of actions from an initial model state and set of commands.
parallel :: (MonadGen gen, MonadTest m) => Range Int -> Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Parallel m state) Source #
Given the initial model state and set of commands, generates prefix actions to be run sequentially, followed by two branches to be run in parallel.
executeSequential :: (MonadTest m, MonadCatch m, HasCallStack) => (forall v. state v) -> Sequential m state -> m () Source #
Executes a list of actions sequentially, verifying that all post-conditions are met and no exceptions are thrown.
To generate a sequence of actions to execute, see the
sequential
combinator in the Hedgehog.Gen module.
executeParallel :: (MonadTest m, MonadCatch m, MonadBaseControl IO m, HasCallStack) => (forall v. state v) -> Parallel m state -> m () Source #
Executes the prefix actions sequentially, then executes the two branches in parallel, verifying that no exceptions are thrown and that there is at least one sequential interleaving where all the post-conditions are met.
To generate parallel actions to execute, see the parallel
combinator in the Hedgehog.Gen module.