hedgehog-0.4: Hedgehog will eat all your bugs.

Safe HaskellNone
LanguageHaskell98

Hedgehog.Internal.State

Contents

Synopsis

Variables

newtype Var Source #

Symbolic variable names.

Constructors

Var Int 

Instances

Eq Var Source # 

Methods

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

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

Num Var Source # 

Methods

(+) :: Var -> Var -> Var #

(-) :: Var -> Var -> Var #

(*) :: Var -> Var -> Var #

negate :: Var -> Var #

abs :: Var -> Var #

signum :: Var -> Var #

fromInteger :: Integer -> Var #

Ord Var Source # 

Methods

compare :: Var -> Var -> Ordering #

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

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

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

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

data Symbolic a where Source #

Symbolic values.

Constructors

Symbolic :: Typeable a => Var -> Symbolic a 

Instances

Eq1 Symbolic Source # 

Methods

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

Ord1 Symbolic Source # 

Methods

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

Show1 Symbolic Source # 

Methods

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

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

Eq (Symbolic a) Source # 

Methods

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

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

Ord (Symbolic a) Source # 

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 # 

Methods

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

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

newtype Concrete a where Source #

Concrete values.

Constructors

Concrete :: a -> Concrete a 

Instances

Functor Concrete Source # 

Methods

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

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

Foldable Concrete Source # 

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 # 

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 # 

Methods

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

Ord1 Concrete Source # 

Methods

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

Show1 Concrete Source # 

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 # 

Methods

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

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

Ord a => Ord (Concrete a) Source # 

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 # 

Methods

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

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

Environment

newtype Environment Source #

A mapping of symbolic values to concrete values.

Constructors

Environment 

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 n m state Source #

The specification for the expected behaviour of an Action.

Constructors

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

Fields

data Callback input output m 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 -> v output -> 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 -> input Concrete -> output -> Test m ())

A post-condition for a command that must be verified for the command to be considered a success.

commandGenOK :: Command n 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)) => Action 

Fields

Instances

Show (Action m state) Source # 

Methods

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

show :: Action m state -> String #

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

takeVariables :: HTraversable t => t Symbolic -> Set Var 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 -> Set Var -> Bool Source #

Checks that the symbolic values in the data structure refer only to the variables in the provided set.

dropInvalid :: (forall v. state v) -> [Action m state] -> [Action m state] Source #

Drops invalid actions from the sequence.

action :: (Monad n, Monad m) => [Command n m state] -> Gen (StateT (state Symbolic, Var) n) (Action m state) Source #

Generates a single action from a set of possible commands.

actions :: (Monad n, Monad m) => Range Int -> (forall v. state v) -> [Command n m state] -> Gen n [Action m state] Source #

Generates a sequence of actions from an initial model state and set of commands.

execute :: (HasCallStack, Monad m) => (state Concrete, Environment) -> Action m state -> Test m (state Concrete, Environment) Source #

Executes a single action in the given evironment.

executeSequential :: forall m state. (HasCallStack, MonadCatch m) => (forall v. state v) -> [Action m state] -> Test 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 actions combinator in the Hedgehog.Gen module.