quickcheck-state-machine-0.9.0: Test monadic programs using state machine based models
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.StateMachine.Lockstep.Simple

Synopsis

Test type-level parameters

type family MockState t :: Type Source #

Mock state

The t argument (here and elsewhere) is a type-level tag that combines all aspects of the test; it does not need any term-level constructors

data MyTest
type instance MockState MyTest = ..

Instances

Instances details
type MockState (Simple t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data family Cmd t :: Type -> Type Source #

Commands

In Cmd t h, h is the type of the handle

Cmd t (RealHandle t)  -- for the system under test
Cmd t (MockHandle t)  -- for the mock

data family Resp t :: Type -> Type Source #

Responses

In Resp t h, h is the type of the handle

Resp t (RealHandle t)  -- for the system under test
Resp t (MockHandle t)  -- for the mock

data family RealHandle t :: Type Source #

The type of the real handle in the system under test

The key difference between the " simple " lockstep infrastructure and the n-ary lockstep infrastructure is that the former only supports a single real handle, whereas the latter supports an arbitrary list of them.

Instances

Instances details
Show (MockHandle t) => Show (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Eq (MockHandle t) => Eq (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Cmd t), Show (Cmd t (Reference (RealHandle t) r)), Show1 r) => Show (Cmd (Simple t) (FlipRef r) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

showsPrec :: Int -> Cmd (Simple t) (FlipRef r) '[RealHandle t] -> ShowS #

show :: Cmd (Simple t) (FlipRef r) '[RealHandle t] -> String #

showList :: [Cmd (Simple t) (FlipRef r) '[RealHandle t]] -> ShowS #

(Functor (Resp t), Show (Resp t (Reference (RealHandle t) r)), Show1 r) => Show (Resp (Simple t) (FlipRef r) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

showsPrec :: Int -> Resp (Simple t) (FlipRef r) '[RealHandle t] -> ShowS #

show :: Resp (Simple t) (FlipRef r) '[RealHandle t] -> String #

showList :: [Resp (Simple t) (FlipRef r) '[RealHandle t]] -> ShowS #

(Functor (Resp t), Show (Resp t (MockHandle t))) => Show (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Resp t), Eq (Resp t (MockHandle t)), Eq (MockHandle t)) => Eq (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

newtype MockHandleN (Simple t) (RealHandle t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data family MockHandle t :: Type Source #

The type of the mock handle

NOTE: In the n-ary infrastructure, MockHandle is a type family of two arguments, because we have a mock handle for each real handle. Here, however, we only have a single real handle, so the " corresponding " real handle is implicitly RealHandle t.

type family Test (f :: Type -> Type) :: Type where ... Source #

Equations

Test (Cmd t) = t 
Test (Resp t) = t 

type family Tag t :: Type Source #

Tags

Tags are used when labelling execution runs in prop_sequential, as well as when looking for minimal examples with a given label (showLabelledExamples).

Instances

Instances details
type Tag (Simple t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

type Tag (Simple t) = Tag t

Test term-level parameters

data StateMachineTest t Source #

State machine test

This captures the design patterns sketched in https://well-typed.com/blog/2019/01/qsm-in-depth/ for the case where there is exactly one real handle. See Test.StateMachine.Lockstep.NAry for the generalization to n handles.

data Event t r Source #

Constructors

Event 

Fields

Handle instantiation

newtype At f r Source #

Constructors

At 

Fields

type (:@) f r = At f r Source #

Model state

data Model t r Source #

Constructors

Model 

Running the tests

prop_sequential Source #

Arguments

:: StateMachineTest t 
-> Maybe Int

(Optional) minimum number of commands

-> Property 

prop_parallel Source #

Arguments

:: StateMachineTest t 
-> Maybe Int

(Optional) minimum number of commands

-> Property 

Translate to n-ary model model

For orphan ToExpr instances

data Simple t Source #

Instances

Instances details
Traversable (Cmd t) => NTraversable (Cmd (Simple t) :: (Type -> Type) -> [Type] -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

nctraverse :: forall m c (xs :: [k]) proxy g h. (Applicative m, All c xs) => proxy c -> (forall (a :: k). c a => Elem xs a -> g a -> m (h a)) -> Cmd (Simple t) g xs -> m (Cmd (Simple t) h xs) Source #

Traversable (Resp t) => NTraversable (Resp (Simple t) :: (Type -> Type) -> [Type] -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

nctraverse :: forall m c (xs :: [k]) proxy g h. (Applicative m, All c xs) => proxy c -> (forall (a :: k). c a => Elem xs a -> g a -> m (h a)) -> Resp (Simple t) g xs -> m (Resp (Simple t) h xs) Source #

Show (MockHandle t) => Show (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Eq (MockHandle t) => Eq (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Cmd t), Show (Cmd t (Reference (RealHandle t) r)), Show1 r) => Show (Cmd (Simple t) (FlipRef r) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

showsPrec :: Int -> Cmd (Simple t) (FlipRef r) '[RealHandle t] -> ShowS #

show :: Cmd (Simple t) (FlipRef r) '[RealHandle t] -> String #

showList :: [Cmd (Simple t) (FlipRef r) '[RealHandle t]] -> ShowS #

(Functor (Resp t), Show (Resp t (Reference (RealHandle t) r)), Show1 r) => Show (Resp (Simple t) (FlipRef r) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

showsPrec :: Int -> Resp (Simple t) (FlipRef r) '[RealHandle t] -> ShowS #

show :: Resp (Simple t) (FlipRef r) '[RealHandle t] -> String #

showList :: [Resp (Simple t) (FlipRef r) '[RealHandle t]] -> ShowS #

(Functor (Resp t), Show (Resp t (MockHandle t))) => Show (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Resp t), Eq (Resp t (MockHandle t)), Eq (MockHandle t)) => Eq (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data Cmd (Simple _1) _f _hs Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data Cmd (Simple _1) _f _hs where
type MockState (Simple t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

type RealHandles (Simple t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

type RealHandles (Simple t) = '[RealHandle t]
data Resp (Simple _1) _f _hs Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data Resp (Simple _1) _f _hs where
type Tag (Simple t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

type Tag (Simple t) = Tag t
newtype MockHandleN (Simple t) (RealHandle t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

data family MockHandleN t a :: Type Source #

Mock handles

For each real handle a, MockHandleN t a is the corresponding mock handle.

Instances

Instances details
Show (MockHandle t) => Show (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Eq (MockHandle t) => Eq (MockHandleN (Simple t) (RealHandle t)) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Resp t), Show (Resp t (MockHandle t))) => Show (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

(Functor (Resp t), Eq (Resp t (MockHandle t)), Eq (MockHandle t)) => Eq (Resp (Simple t) (MockHandleN (Simple t)) '[RealHandle t]) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

newtype MockHandleN (Simple t) (RealHandle t) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple