Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simple (stateful) Model-Based Testing library for use with Haskell QuickCheck.
This module provides the basic machinery to define a StateModel
from which traces can
be generated and executed against some actual implementation code to define monadic Property
to be asserted by QuickCheck.
Synopsis
- class (forall a. Show (Action state a), Show state) => StateModel state where
- data Action state a
- actionName :: Action state a -> String
- arbitraryAction :: state -> Gen (Any (Action state))
- shrinkAction :: (Show a, Typeable a) => state -> Action state a -> [Any (Action state)]
- initialState :: state
- nextState :: state -> Action state a -> Var a -> state
- precondition :: state -> Action state a -> Bool
- postcondition :: state -> Action state a -> LookUp -> a -> Bool
- monitoring :: (state, state) -> Action state a -> LookUp -> a -> Property -> Property
- newtype RunModel state m = RunModel {}
- data Any f where
- data Step state where
- type LookUp = forall a. Typeable a => Var a -> a
- newtype Var a = Var Int
- data Actions state = Actions_ [String] (Smart [Step state])
- pattern Actions :: [Step state] -> Actions state
- data EnvEntry where
- type Env = [EnvEntry]
- stateAfter :: StateModel state => Actions state -> state
- runActions :: forall state m. (StateModel state, Monad m) => RunModel state m -> Actions state -> PropertyM m (state, Env)
- runActionsInState :: forall state m. (StateModel state, Monad m) => state -> RunModel state m -> Actions state -> PropertyM m (state, Env)
- lookUpVar :: Typeable a => Env -> Var a -> a
- lookUpVarMaybe :: Typeable a => Env -> Var a -> Maybe a
- invertLookupVarMaybe :: (Typeable a, Eq a) => Env -> a -> Maybe (Var a)
Documentation
class (forall a. Show (Action state a), Show state) => StateModel state where Source #
The typeclass users implement to define a model against which to validate some implementation.
To implement a StateModel
, user needs to provide at least the following:
- A datatype for
Action
s: Each test case is a sequence ofAction
s that's supposed to lead from someinitialState
to some end state, - A generator for traces of
Action
s, thearbitraryAction
function, - An
initialState
, - A transition function,
nextState
, that "interprets" eachAction
and producing some newstate
.
For finer grained control over the testing process, one can also define:
shrinkAction
: Shrinking is an important part of MBT as it allows QuickCheck engine to look for simpler test cases when something goes wrong which makes troubleshooting easier,precondition
: Filters generatedAction
depending on thestate
. Whenprecondition
is False then the action is rejected and a new one is tried. This is also useful when shrinking a trace in order to ensure that removing someAction
still produces a valid trace. Theprecondition
can be somewhat redundant with the generator's conditions,postcondition
: This function is evaluated during test execution afterperform
ing the action, it allows the model to express expectations about the output of actual code given some "transition".
The type of Action
relevant for this state
.
This is expected to be defined as a GADT where the a
parameter is instantiated to some
observable output from the SUT a given action is expected to produce. For example, here
is a fragment of the `Action RegState` (taken from the RegistryModel
module) :
data Action RegState a where Spawn :: Action RegState ThreadId Register :: String -> Var ThreadId -> Action RegState (Either ErrorCall ()) KillThread :: Var ThreadId -> Action RegState ()
The Spawn
action should produce a ThreadId
, whereas the KillThread
action does not return
anything.
actionName :: Action state a -> String Source #
Display name for Action
.
This is useful to provide sensible statistics about the distribution of Action
s run
when checking a property.
Default implementation uses a poor-man's string manipulation method to extract the constructor name from the value.
arbitraryAction :: state -> Gen (Any (Action state)) Source #
Generator for Action
depending on state
.
The generated values are wrapped in Any
type to allow the model to not generate an action under
some circumstances: Any generated Error
value will be ignored when generating a trace for testing.
shrinkAction :: (Show a, Typeable a) => state -> Action state a -> [Any (Action state)] Source #
Shrinker for Action
.
Defaults to no-op but as usual, defining a good shrinker greatly enhances the usefulness
of property-based testing.
initialState :: state Source #
Initial state of generated traces.
nextState :: state -> Action state a -> Var a -> state Source #
Transition function for the model.
The `Var a` parameter is useful to keep reference to actual value of type a
produced
by perform
ing the Action
inside the state
so that further actions can use Lookup
to retrieve that data. This allows the model to be ignorant of those values yet maintain
some references that can be compared and looked for.
precondition :: state -> Action state a -> Bool Source #
Precondition for filtering generated Action
.
This function is applied before the action is performed, it is useful to refine generators that
can produce more values than are useful.
postcondition :: state -> Action state a -> LookUp -> a -> Bool Source #
Postcondition on the a
value produced at some step.
The result is assert
ed and will make the property fail should it be False
. This is useful
to check the implementation produces expected values.
monitoring :: (state, state) -> Action state a -> LookUp -> a -> Property -> Property Source #
newtype RunModel state m Source #
Perform an Action
in some state
in the Monad
m
. This
is the function that's used to exercise the actual stateful
implementation, usually through various side-effects as permitted
by m
. It produces a value of type a
, eg. some observable
output from the Action
that should later be kept in the
environment through a `Var a` also passed to the nextState
function.
The Lookup
parameter provides an environment to lookup `Var
a` instances from previous steps.
data Step state where Source #
(:=) :: (Show a, Typeable a, Eq (Action state a), Show (Action state a)) => Var a -> Action state a -> Step state infix 5 |
Instances
Eq (Var a) Source # | |
Data a => Data (Var a) Source # | |
Defined in Test.QuickCheck.StateModel gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var a -> c (Var a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Var a) # dataTypeOf :: Var a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Var a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Var a)) # gmapT :: (forall b. Data b => b -> b) -> Var a -> Var a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var a -> r # gmapQ :: (forall d. Data d => d -> u) -> Var a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var a -> m (Var a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var a -> m (Var a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var a -> m (Var a) # | |
Ord (Var a) Source # | |
Show (Var a) Source # | |
stateAfter :: StateModel state => Actions state -> state Source #
runActions :: forall state m. (StateModel state, Monad m) => RunModel state m -> Actions state -> PropertyM m (state, Env) Source #
runActionsInState :: forall state m. (StateModel state, Monad m) => state -> RunModel state m -> Actions state -> PropertyM m (state, Env) Source #