hedgehog-1.0.2: Release with confidence.

Safe HaskellNone
LanguageHaskell98

Hedgehog.Internal.State

Contents

Synopsis

Variables

newtype Var a v Source #

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.

Constructors

Var (v a) 
Instances
HTraversable (Var a) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

htraverse :: Applicative f => (forall a0. g a0 -> f (h a0)) -> Var a g -> f (Var a h) Source #

(Eq a, Eq1 v) => Eq (Var a v) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

(==) :: Var a v -> Var a v -> Bool #

(/=) :: Var a v -> Var a v -> Bool #

(Ord a, Ord1 v) => Ord (Var a v) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

compare :: Var a v -> Var a v -> Ordering #

(<) :: Var a v -> Var a v -> Bool #

(<=) :: Var a v -> Var a v -> Bool #

(>) :: Var a v -> Var a v -> Bool #

(>=) :: Var a v -> Var a v -> Bool #

max :: Var a v -> Var a v -> Var a v #

min :: Var a v -> Var a v -> Var a v #

(Show a, Show1 v) => Show (Var a v) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Var a v -> ShowS #

show :: Var a v -> String #

showList :: [Var a v] -> ShowS #

concrete :: Var a Concrete -> a Source #

Take the value from a concrete variable.

opaque :: Var (Opaque a) Concrete -> a Source #

Take the value from an opaque concrete variable.

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.

Constructors

Concrete :: a -> Concrete a 
Instances
Functor Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

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

Foldable Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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 #

toList :: Concrete a -> [a] #

null :: Concrete a -> Bool #

length :: Concrete a -> Int #

elem :: Eq a => a -> Concrete a -> Bool #

maximum :: Ord a => Concrete a -> a #

minimum :: Ord a => Concrete a -> a #

sum :: Num a => Concrete a -> a #

product :: Num a => Concrete a -> a #

Traversable Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

traverse :: Applicative f => (a -> f b) -> Concrete a -> f (Concrete b) #

sequenceA :: Applicative f => Concrete (f a) -> f (Concrete a) #

mapM :: Monad m => (a -> m b) -> Concrete a -> m (Concrete b) #

sequence :: Monad m => Concrete (m a) -> m (Concrete a) #

Eq1 Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

Ord1 Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

Show1 Concrete Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

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

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

Defined in Hedgehog.Internal.State

Methods

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

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

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

Defined in Hedgehog.Internal.State

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 #

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

Defined in Hedgehog.Internal.State

Methods

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

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

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).

Symbolic 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.

See also: Command, Var

Constructors

Symbolic :: Typeable a => Name -> Symbolic a 
Instances
Eq1 Symbolic Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

Ord1 Symbolic Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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

Show1 Symbolic Source # 
Instance details

Defined in Hedgehog.Internal.State

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 Hedgehog.Internal.State

Methods

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

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

Ord (Symbolic a) Source # 
Instance details

Defined in Hedgehog.Internal.State

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 Hedgehog.Internal.State

Methods

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

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

newtype Name Source #

Symbolic variable names.

Constructors

Name Int 
Instances
Eq Name Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Num Name Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

(+) :: Name -> Name -> Name #

(-) :: Name -> Name -> Name #

(*) :: Name -> Name -> Name #

negate :: Name -> Name #

abs :: Name -> Name #

signum :: Name -> Name #

fromInteger :: Integer -> Name #

Ord Name Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Environment

newtype Environment Source #

A mapping of symbolic values to concrete values.

Constructors

Environment 
Instances
Show Environment Source # 
Instance details

Defined in Hedgehog.Internal.State

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.

Constructors

(HTraversable input, Show (input Symbolic), Show output, Typeable output) => Command 

Fields

  • commandGen :: state Symbolic -> Maybe (gen (input Symbolic))

    A generator which provides random arguments for a command. If the command cannot be executed in the current state, it should return Nothing.

  • commandExecute :: input Concrete -> m output

    Executes a command using the arguments generated by commandGen.

  • commandCallbacks :: [Callback input output state]

    A set of callbacks which provide optional command configuration such as pre-condtions, post-conditions and state updates.

data Callback input output state Source #

Optional command configuration.

Constructors

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 Symbolic values when we are generating actions, and Concrete values when we are executing them.

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.

Constructors

(HTraversable input, Show (input Symbolic), Show output) => Action 

Fields

Instances
Show (Action m state) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Action m state -> ShowS #

show :: Action m state -> String #

showList :: [Action m state] -> ShowS #

data Sequential m state Source #

A sequence of actions to execute.

Constructors

Sequential 

Fields

Instances
Show (Sequential m state) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

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.

Constructors

Parallel 

Fields

Instances
Show (Parallel m state) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

showsPrec :: Int -> Parallel m state -> ShowS #

show :: Parallel m state -> String #

showList :: [Parallel m state] -> ShowS #

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.