quickcheck-state-machine-0.7.0: Test monadic programs using state machine based models

Safe HaskellNone
LanguageHaskell2010

Test.StateMachine.Lockstep.NAry

Contents

Synopsis

Test type-level parameters

type family MockState t :: Type Source #

data family Cmd t :: (Type -> Type) -> [Type] -> Type Source #

Instances
(NTraversable (Cmd t), SListI (RealHandles t)) => Traversable (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

traverse :: Applicative f => (forall (a :: k). p a -> f (q a)) -> At (Cmd t) p -> f (At (Cmd t) q) Source #

(NTraversable (Cmd t), SListI (RealHandles t)) => Foldable (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> At (Cmd t) p -> m Source #

(NTraversable (Cmd t), SListI (RealHandles t)) => Functor (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

fmap :: (forall (x :: k). p x -> q x) -> At (Cmd t) p -> At (Cmd t) q Source #

data family Resp t :: (Type -> Type) -> [Type] -> Type Source #

Instances
(NTraversable (Resp t), SListI (RealHandles t)) => Traversable (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

traverse :: Applicative f => (forall (a :: k). p a -> f (q a)) -> At (Resp t) p -> f (At (Resp t) q) Source #

(NTraversable (Resp t), SListI (RealHandles t)) => Foldable (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> At (Resp t) p -> m Source #

(NTraversable (Resp t), SListI (RealHandles t)) => Functor (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

fmap :: (forall (x :: k). p x -> q x) -> At (Resp t) p -> At (Resp t) q Source #

type family RealHandles t :: [Type] Source #

data family MockHandle t a :: Type Source #

type family RealMonad t :: Type -> Type Source #

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

Equations

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

Test term-level parameters

Handle instantiation

newtype At f r Source #

Constructors

At 

Fields

Instances
(NTraversable (Resp t), SListI (RealHandles t)) => Traversable (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

traverse :: Applicative f => (forall (a :: k). p a -> f (q a)) -> At (Resp t) p -> f (At (Resp t) q) Source #

(NTraversable (Cmd t), SListI (RealHandles t)) => Traversable (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

traverse :: Applicative f => (forall (a :: k). p a -> f (q a)) -> At (Cmd t) p -> f (At (Cmd t) q) Source #

(NTraversable (Resp t), SListI (RealHandles t)) => Foldable (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> At (Resp t) p -> m Source #

(NTraversable (Cmd t), SListI (RealHandles t)) => Foldable (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> At (Cmd t) p -> m Source #

(NTraversable (Resp t), SListI (RealHandles t)) => Functor (At (Resp t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

fmap :: (forall (x :: k). p x -> q x) -> At (Resp t) p -> At (Resp t) q Source #

(NTraversable (Cmd t), SListI (RealHandles t)) => Functor (At (Cmd t) :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

fmap :: (forall (x :: k). p x -> q x) -> At (Cmd t) p -> At (Cmd t) q Source #

Show (f (FlipRef r) (RealHandles (Test f))) => Show (At f r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

showsPrec :: Int -> At f r -> ShowS #

show :: At f r -> String #

showList :: [At f r] -> ShowS #

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

Model state

data Model t r Source #

Constructors

Model 

Fields

Instances
(Show1 r, Show (MockState t), All (And Show (Compose Show (MockHandle t))) (RealHandles t)) => Show (Model t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

showsPrec :: Int -> Model t r -> ShowS #

show :: Model t r -> String #

showList :: [Model t r] -> ShowS #

Generic (Model t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Associated Types

type Rep (Model t r) :: Type -> Type #

Methods

from :: Model t r -> Rep (Model t r) x #

to :: Rep (Model t r) x -> Model t r #

(ToExpr (MockState t), All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t)) => ToExpr (Model t Concrete) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

type Rep (Model t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

type Rep (Model t r) = D1 (MetaData "Model" "Test.StateMachine.Lockstep.NAry" "quickcheck-state-machine-0.7.0-BWWTJ8RJVPk3Dmgg7XSpMH" 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))))

newtype Refs t r a Source #

Relation between real and mock references for single handle type a

Constructors

Refs 

Fields

Instances
(Show1 r, Show a, Show (MockHandle t a)) => Show (Refs t r a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

showsPrec :: Int -> Refs t r a -> ShowS #

show :: Refs t r a -> String #

showList :: [Refs t r a] -> ShowS #

Generic (Refs t r a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Associated Types

type Rep (Refs t r a) :: Type -> Type #

Methods

from :: Refs t r a -> Rep (Refs t r a) x #

to :: Rep (Refs t r a) x -> Refs t r a #

Semigroup (Refs t r a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

(<>) :: Refs t r a -> Refs t r a -> Refs t r a #

sconcat :: NonEmpty (Refs t r a) -> Refs t r a #

stimes :: Integral b => b -> Refs t r a -> Refs t r a #

Monoid (Refs t r a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

mempty :: Refs t r a #

mappend :: Refs t r a -> Refs t r a -> Refs t r a #

mconcat :: [Refs t r a] -> Refs t r a #

(ToExpr a, ToExpr (MockHandle t a)) => ToExpr (Refs t Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

toExpr :: Refs t Concrete a -> Expr #

listToExpr :: [Refs t Concrete a] -> Expr #

type Rep (Refs t r a) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

type Rep (Refs t r a) = Rep [(Reference a r, MockHandle t a)]

newtype Refss t r Source #

Relation between real and mock references for all handle types

Constructors

Refss 

Fields

Instances
(Show1 r, All (And Show (Compose Show (MockHandle t))) (RealHandles t)) => Show (Refss t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

showsPrec :: Int -> Refss t r -> ShowS #

show :: Refss t r -> String #

showList :: [Refss t r] -> ShowS #

SListI (RealHandles t) => Semigroup (Refss t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

(<>) :: Refss t r -> Refss t r -> Refss t r #

sconcat :: NonEmpty (Refss t r) -> Refss t r #

stimes :: Integral b => b -> Refss t r -> Refss t r #

SListI (RealHandles t) => Monoid (Refss t r) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

mempty :: Refss t r #

mappend :: Refss t r -> Refss t r -> Refss t r #

mconcat :: [Refss t r] -> Refss t r #

All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t) => ToExpr (Refss t Concrete) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

newtype FlipRef r h Source #

Constructors

FlipRef 

Fields

Instances
(Show1 r, Show h) => Show (FlipRef r h) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.NAry

Methods

showsPrec :: Int -> FlipRef r h -> ShowS #

show :: FlipRef r h -> String #

showList :: [FlipRef r h] -> ShowS #

Running the tests

prop_sequential Source #

Arguments

:: RealMonad t ~ IO 
=> StateMachineTest t 
-> Maybe Int

(Optional) minimum number of commands

-> Property 

prop_parallel Source #

Arguments

:: RealMonad t ~ IO 
=> StateMachineTest t 
-> Maybe Int

(Optional) minimum number of commands

-> Property