quickcheck-dynamic-1.1.0: A library for stateful property-based testing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.QuickCheck.StateModel

Description

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

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:

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 generated Action depending on the state. When precondition 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 some Action still produces a valid trace. The precondition can be somewhat redundant with the generator's conditions,
  • postcondition: This function is evaluated during test execution after performing the action, it allows the model to express expectations about the output of actual code given some "transition".

Minimal complete definition

arbitraryAction, initialState

Associated Types

data Action state a Source #

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.

Methods

actionName :: Action state a -> String Source #

Display name for Action. This is useful to provide sensible statistics about the distribution of Actions 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 performing 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 asserted and will make the property fail should it be False. This is useful to check the implementation produces expected values.

monitoring :: Show a => (state, state) -> Action state a -> LookUp -> a -> Property -> Property Source #

Allows the user to attach information to the Property at each step of the process. This function is given the full transition that's been executed, including the start and ending state, the Action, the current environment to Lookup and the value produced by perform while executing this step.

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.

Constructors

RunModel 

Fields

data Any f where Source #

Constructors

Some :: (Show a, Typeable a, Eq (f a)) => f a -> Any f 
Error :: String -> Any f 

Instances

Instances details
(forall a. Show (Action state a)) => Show (Any (Action state)) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

showsPrec :: Int -> Any (Action state) -> ShowS #

show :: Any (Action state) -> String #

showList :: [Any (Action state)] -> ShowS #

Eq (Any f) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

(==) :: Any f -> Any f -> Bool #

(/=) :: Any f -> Any f -> Bool #

data Step state where Source #

Constructors

(:=) :: (Show a, Typeable a, Eq (Action state a), Show (Action state a)) => Var a -> Action state a -> Step state infix 5 

Instances

Instances details
(forall a. Show (Action state a)) => Show (Step state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

showsPrec :: Int -> Step state -> ShowS #

show :: Step state -> String #

showList :: [Step state] -> ShowS #

Eq (Step state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

(==) :: Step state -> Step state -> Bool #

(/=) :: Step state -> Step state -> Bool #

type LookUp = forall a. Typeable a => Var a -> a Source #

newtype Var a Source #

Constructors

Var Int 

Instances

Instances details
Data a => Data (Var a) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

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

toConstr :: Var a -> Constr #

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

Show (Var a) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

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

show :: Var a -> String #

showList :: [Var a] -> ShowS #

Eq (Var a) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

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

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

Ord (Var a) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

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

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

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

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

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

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

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

data Actions state Source #

Constructors

Actions_ [String] (Smart [Step state]) 

Instances

Instances details
StateModel state => Arbitrary (Actions state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

arbitrary :: Gen (Actions state) #

shrink :: Actions state -> [Actions state] #

Semigroup (Actions state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

(<>) :: Actions state -> Actions state -> Actions state #

sconcat :: NonEmpty (Actions state) -> Actions state #

stimes :: Integral b => b -> Actions state -> Actions state #

(forall a. Show (Action state a)) => Show (Actions state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

showsPrec :: Int -> Actions state -> ShowS #

show :: Actions state -> String #

showList :: [Actions state] -> ShowS #

Eq (Actions state) Source # 
Instance details

Defined in Test.QuickCheck.StateModel

Methods

(==) :: Actions state -> Actions state -> Bool #

(/=) :: Actions state -> Actions state -> Bool #

pattern Actions :: [Step state] -> Actions state Source #

data EnvEntry where Source #

Constructors

(:==) :: (Show a, Typeable a) => Var a -> a -> EnvEntry infix 5 

Instances

Instances details
Show EnvEntry Source # 
Instance details

Defined in Test.QuickCheck.StateModel

type Env = [EnvEntry] 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 #

lookUpVar :: Typeable a => Env -> Var a -> a Source #

invertLookupVarMaybe :: (Typeable a, Eq a) => Env -> a -> Maybe (Var a) Source #