module Test.QuickCheck.StateModel.Lockstep.API (
Lockstep(..)
, getModel
, InLockstep(..)
, RunLockstep(..)
, LockstepAction
, ModelFindVariables
, ModelLookUp
, ModelVar
, ModelShrinkVar
, RealLookUp
, ModelVarContext
, findVars
, lookupVar
, shrinkVar
, realLookupVar
) where
import Data.Constraint (Dict(..))
import Data.Kind
import Data.Typeable
import Test.QuickCheck (Gen)
import Test.QuickCheck.StateModel (StateModel, Any, RunModel, Realized, Action, LookUp)
import Test.QuickCheck.StateModel.Lockstep.EnvF (EnvF)
import Test.QuickCheck.StateModel.Lockstep.GVar (GVar, AnyGVar(..), fromVar)
import Test.QuickCheck.StateModel.Lockstep.Op
import Test.QuickCheck.StateModel.Lockstep.Op.Identity qualified as Identity
import Test.QuickCheck.StateModel.Lockstep.EnvF qualified as EnvF
import Test.QuickCheck.StateModel.Lockstep.GVar qualified as EnvF
data Lockstep state = Lockstep {
forall state. Lockstep state -> state
lockstepModel :: state
, forall state. Lockstep state -> EnvF (ModelValue state)
lockstepEnv :: EnvF (ModelValue state)
}
instance Show state => Show (Lockstep state) where
show :: Lockstep state -> String
show = state -> String
forall a. Show a => a -> String
show (state -> String)
-> (Lockstep state -> state) -> Lockstep state -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lockstep state -> state
forall state. Lockstep state -> state
lockstepModel
getModel :: Lockstep state -> state
getModel :: forall state. Lockstep state -> state
getModel = Lockstep state -> state
forall state. Lockstep state -> state
lockstepModel
class
( StateModel (Lockstep state)
, Typeable state
, InterpretOp (ModelOp state) (ModelValue state)
, forall a. Show (ModelValue state a)
, forall a. Eq (Observable state a)
, forall a. Show (Observable state a)
)
=> InLockstep state where
data ModelValue state a
data Observable state a
type ModelOp state :: Type -> Type -> Type
type ModelOp state = Identity.Op
observeModel :: ModelValue state a-> Observable state a
usedVars :: LockstepAction state a -> [AnyGVar (ModelOp state)]
modelNextState ::
LockstepAction state a
-> ModelVarContext state
-> state
-> (ModelValue state a, state)
arbitraryWithVars ::
ModelVarContext state
-> state
-> Gen (Any (LockstepAction state))
shrinkWithVars ::
ModelVarContext state
-> state
-> LockstepAction state a
-> [Any (LockstepAction state)]
shrinkWithVars ModelVarContext state
_ state
_ LockstepAction state a
_ = []
tagStep ::
(state, state)
-> LockstepAction state a
-> ModelValue state a
-> [String]
tagStep (state, state)
_ LockstepAction state a
_ ModelValue state a
_ = []
class ( InLockstep state
, RunModel (Lockstep state) m
) => RunLockstep state m where
observeReal ::
Proxy m
-> LockstepAction state a -> Realized m a -> Observable state a
showRealResponse ::
Proxy m
-> LockstepAction state a
-> Maybe (Dict (Show (Realized m a)))
showRealResponse Proxy m
_ LockstepAction state a
_ = Maybe (Dict (Show (Realized m a)))
forall a. Maybe a
Nothing
type LockstepAction state = Action (Lockstep state)
type ModelLookUp state = forall a. ModelVar state a -> ModelValue state a
type ModelFindVariables state = forall a.
Typeable a
=> Proxy a -> [GVar (ModelOp state) a]
type ModelShrinkVar state = forall a. ModelVar state a -> [ModelVar state a]
type RealLookUp m op = forall a. Proxy m -> LookUp m -> GVar op a -> Realized m a
type ModelVar state = GVar (ModelOp state)
type ModelVarContext state = EnvF (ModelValue state)
findVars ::
InLockstep state
=> ModelVarContext state -> ModelFindVariables state
findVars :: forall state.
InLockstep state =>
ModelVarContext state -> ModelFindVariables state
findVars ModelVarContext state
env Proxy a
_ = (Var a -> GVar (ModelOp state) a)
-> [Var a] -> [GVar (ModelOp state) a]
forall a b. (a -> b) -> [a] -> [b]
map Var a -> GVar (ModelOp state) a
forall (op :: * -> * -> *) a.
(Operation op, Typeable a) =>
Var a -> GVar op a
fromVar ([Var a] -> [GVar (ModelOp state) a])
-> [Var a] -> [GVar (ModelOp state) a]
forall a b. (a -> b) -> a -> b
$ ModelVarContext state -> [Var a]
forall a (f :: * -> *). Typeable a => EnvF f -> [Var a]
EnvF.keysOfType ModelVarContext state
env
lookupVar ::
InLockstep state
=> ModelVarContext state -> ModelLookUp state
lookupVar :: forall state.
InLockstep state =>
ModelVarContext state -> ModelLookUp state
lookupVar ModelVarContext state
env ModelVar state a
gvar = case ModelVarContext state
-> ModelVar state a -> Maybe (ModelValue state a)
forall (f :: * -> *) (op :: * -> * -> *) a.
(Typeable f, InterpretOp op f) =>
EnvF f -> GVar op a -> Maybe (f a)
EnvF.lookUpEnvF ModelVarContext state
env ModelVar state a
gvar of
Just ModelValue state a
x -> ModelValue state a
x
Maybe (ModelValue state a)
Nothing -> String -> ModelValue state a
forall a. HasCallStack => String -> a
error
String
"lookupVar: the variable (ModelVar) must be well-defined and evaluable, \
\but this requirement was violated. Normally, this is guaranteed by the \
\default test 'precondition'."
shrinkVar ::
(Typeable state, InterpretOp (ModelOp state) (ModelValue state))
=> ModelVarContext state -> ModelShrinkVar state
shrinkVar :: forall state.
(Typeable state, InterpretOp (ModelOp state) (ModelValue state)) =>
ModelVarContext state -> ModelShrinkVar state
shrinkVar ModelVarContext state
env ModelVar state a
var = ModelVarContext state -> ModelVar state a -> [ModelVar state a]
forall (f :: * -> *) (op :: * -> * -> *) a.
(Typeable f, InterpretOp op f) =>
EnvF f -> GVar op a -> [GVar op a]
EnvF.shrinkGVar ModelVarContext state
env ModelVar state a
var
realLookupVar :: InterpretOp op (WrapRealized m) => RealLookUp m op
realLookupVar :: forall (op :: * -> * -> *) (m :: * -> *).
InterpretOp op (WrapRealized m) =>
RealLookUp m op
realLookupVar Proxy m
p LookUp m
lookUp GVar op a
gvar = case Proxy m -> LookUp m -> GVar op a -> Maybe (Realized m a)
forall (op :: * -> * -> *) (m :: * -> *) a.
InterpretOp op (WrapRealized m) =>
Proxy m -> LookUp m -> GVar op a -> Maybe (Realized m a)
EnvF.lookUpGVar Proxy m
p Var a -> Realized m a
LookUp m
lookUp GVar op a
gvar of
Just Realized m a
x -> Realized m a
x
Maybe (Realized m a)
Nothing -> String -> Realized m a
forall a. HasCallStack => String -> a
error
String
"realLookupVar: the variable (GVar) must be well-defined and evaluable, \
\but this requirement was violated. Normally, this is guaranteed by the \
\default test 'precondition'."