Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family MockState t :: Type
- data family Cmd t :: (Type -> Type) -> [Type] -> Type
- data family Resp t :: (Type -> Type) -> [Type] -> Type
- type family RealHandles t :: [Type]
- data family MockHandleN t a :: Type
- type family Test (f :: (Type -> Type) -> [Type] -> Type) :: Type where ...
- type family Tag t :: Type
- data StateMachineTest t m = (Monad m, All Typeable (RealHandles t), All Eq (RealHandles t), All (And Show (Compose Show (MockHandleN t))) (RealHandles t), All (And CanDiff (Compose CanDiff (MockHandleN t))) (RealHandles t), NTraversable (Resp t), Eq (Resp t (MockHandleN t) (RealHandles t)), Show (Resp t (MockHandleN t) (RealHandles t)), Show (Resp t (FlipRef Symbolic) (RealHandles t)), Show (Resp t (FlipRef Concrete) (RealHandles t)), NTraversable (Cmd t), Show (Cmd t (FlipRef Symbolic) (RealHandles t)), Show (Cmd t (FlipRef Concrete) (RealHandles t)), Show (MockState t), CanDiff (MockState t), Show (Tag t), CanDiff (Model t Concrete)) => StateMachineTest {
- runMock :: Cmd t (MockHandleN t) (RealHandles t) -> MockState t -> (Resp t (MockHandleN t) (RealHandles t), MockState t)
- runReal :: Cmd t I (RealHandles t) -> m (Resp t I (RealHandles t))
- initMock :: MockState t
- newHandles :: forall f. Resp t f (RealHandles t) -> NP (List :.: f) (RealHandles t)
- generator :: Model t Symbolic -> Maybe (Gen (Cmd t :@ Symbolic))
- shrinker :: Model t Symbolic -> (Cmd t :@ Symbolic) -> [Cmd t :@ Symbolic]
- cleanup :: Model t Concrete -> m ()
- tag :: [Event t Symbolic] -> [Tag t]
- data Event t r = Event {}
- hoistStateMachineTest :: Monad n => (forall a. m a -> n a) -> StateMachineTest t m -> StateMachineTest t n
- newtype At f r = At {
- unAt :: f (FlipRef r) (RealHandles (Test f))
- type (:@) f r = At f r
- data Model t r = Model {
- modelState :: MockState t
- modelRefss :: Refss t r
- newtype Refs t r a = Refs {
- unRefs :: [(Reference a r, MockHandleN t a)]
- newtype Refss t r = Refss {
- unRefss :: NP (Refs t r) (RealHandles t)
- newtype FlipRef r h = FlipRef {}
- prop_sequential :: forall t. StateMachineTest t IO -> Maybe Int -> Property
- prop_parallel :: StateMachineTest t IO -> Maybe Int -> Property
- showLabelledExamples' :: StateMachineTest t m -> Maybe Int -> Int -> (Tag t -> Bool) -> IO ()
- showLabelledExamples :: StateMachineTest t m -> IO ()
- toStateMachine :: StateMachineTest t m -> StateMachine (Model t) (At (Cmd t)) m (At (Resp t))
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 = ..
data family Cmd t :: (Type -> Type) -> [Type] -> Type Source #
Commands
In Cmd t f hs
, hs
is the list of real handle types, and f
is some
functor applied to each of them. Two typical instantiations are
Cmd t I (RealHandles t) -- for the system under test Cmd t (MockHandleN t) (RealHandles t) -- for the mock
Instances
Traversable (Cmd t) => NTraversable (Cmd (Simple t) :: (Type -> Type) -> [Type] -> Type) Source # | |
Defined in Test.StateMachine.Lockstep.Simple 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 # | |
(NTraversable (Cmd t), SListI (RealHandles t)) => Foldable (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Cmd t), SListI (RealHandles t)) => Functor (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Cmd t), SListI (RealHandles t)) => Traversable (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
Defined in Test.StateMachine.Lockstep.NAry | |
(Functor (Cmd t), Show (Cmd t (Reference (RealHandle t) r)), Show1 r) => Show (Cmd (Simple t) (FlipRef r) '[RealHandle t]) Source # | |
data Cmd (Simple _1) _f _hs Source # | |
data family Resp t :: (Type -> Type) -> [Type] -> Type Source #
Responses
The type arguments are similar to those of Cmd
. Two typical instances:
Resp t I (RealHandles t) -- for the system under test Resp t (MockHandleN t) (RealHandles t) -- for the mock
Instances
type family RealHandles t :: [Type] Source #
Type-level list of the types of the handles in the system under test
NOTE: If your system under test only requires a single real handle, you might consider using Test.StateMachine.Lockstep.Simple instead.
Instances
type RealHandles (Simple t) Source # | |
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
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
).
Test term-level parameters
data StateMachineTest t m Source #
State machine test
This captures the design patterns sketched in https://well-typed.com/blog/2019/01/qsm-in-depth/.
hoistStateMachineTest :: Monad n => (forall a. m a -> n a) -> StateMachineTest t m -> StateMachineTest t n Source #
Handle instantiation
At | |
|
Instances
(NTraversable (Cmd t), SListI (RealHandles t)) => Foldable (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Resp t), SListI (RealHandles t)) => Foldable (At (Resp t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Cmd t), SListI (RealHandles t)) => Functor (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Resp t), SListI (RealHandles t)) => Functor (At (Resp t) :: (Type -> Type) -> Type) Source # | |
(NTraversable (Cmd t), SListI (RealHandles t)) => Traversable (At (Cmd t) :: (Type -> Type) -> Type) Source # | |
Defined in Test.StateMachine.Lockstep.NAry | |
(NTraversable (Resp t), SListI (RealHandles t)) => Traversable (At (Resp t) :: (Type -> Type) -> Type) Source # | |
Defined in Test.StateMachine.Lockstep.NAry | |
Show (f (FlipRef r) (RealHandles (Test f))) => Show (At f r) Source # | |
Model state
Model | |
|
Instances
Generic (Model t r) Source # | |
(Show1 r, Show (MockState t), All (And Show (Compose Show (MockHandleN t))) (RealHandles t)) => Show (Model t r) Source # | |
type Rep (Model t r) Source # | |
Defined in Test.StateMachine.Lockstep.NAry type Rep (Model t r) = D1 ('MetaData "Model" "Test.StateMachine.Lockstep.NAry" "quickcheck-state-machine-0.9.0-8zWHYIJYc77JtQ2efkvn1E-no-vendored-treediff" 'False) (C1 ('MetaCons "Model" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState t)) :*: S1 ('MetaSel ('Just "modelRefss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Refss t r)))) |
Relation between real and mock references for single handle type a
Refs | |
|
Relation between real and mock references for all handle types
Refss | |
|
Instances
(Show1 r, Show h) => Show (FlipRef r h) Source # | |
(Functor (Cmd t), Show (Cmd t (Reference (RealHandle t) r)), Show1 r) => Show (Cmd (Simple t) (FlipRef r) '[RealHandle t]) Source # | |
(Functor (Resp t), Show (Resp t (Reference (RealHandle t) r)), Show1 r) => Show (Resp (Simple t) (FlipRef r) '[RealHandle t]) Source # | |
Running the tests
:: forall t. StateMachineTest t IO | |
-> Maybe Int | (Optional) minimum number of commands |
-> Property |
Sequential test
:: StateMachineTest t IO | |
-> Maybe Int | (Optional) minimum number of commands |
-> Property |
Parallel test
NOTE: This currently does not do labelling.
Examples
showLabelledExamples' Source #
:: StateMachineTest t m | |
-> Maybe Int | Seed |
-> Int | Number of tests to run to find examples |
-> (Tag t -> Bool) | Tag filter (can be |
-> IO () |
Show minimal examples for each of the generated tags.
This is the analogue of showLabelledExamples'
.
See also showLabelledExamples
.
showLabelledExamples :: StateMachineTest t m -> IO () Source #
Simplified form of showLabelledExamples'
Translate to state machine model
toStateMachine :: StateMachineTest t m -> StateMachine (Model t) (At (Cmd t)) m (At (Resp t)) Source #