quickcheck-contractmodel-0.1.4.1
Safe HaskellNone
LanguageHaskell2010

Test.QuickCheck.ContractModel

Synopsis

Documentation

class (Typeable state, Show state, HasActions state) => ContractModel state where Source #

A ContractModel instance captures everything that is needed to generate and run tests of a contract or set of contracts. It specifies among other things

  • what operations are supported by the contract (Action),
  • when they are valid (precondition),
  • how to generate random actions (arbitraryAction),
  • how the operations affect the state (nextState), and
  • how to run the operations in the emulator (perform)

Minimal complete definition

arbitraryAction, initialState, nextState

Associated Types

data Action state Source #

The type of actions that are supported by the contract. An action usually represents a single callEndpoint or a transfer of tokens, but it can be anything that can be interpreted in the EmulatorTrace monad.

Methods

arbitraryAction :: ModelState state -> Gen (Action state) Source #

Given the current model state, provide a QuickCheck generator for a random next action. This is used in the Arbitrary instance for Actionss as well as by anyAction and anyActions.

actionName :: Action state -> String Source #

The name of an Action, used to report statistics.

waitProbability :: ModelState state -> Double Source #

The probability that we will generate a WaitUntil in a given state

arbitraryWaitInterval :: ModelState state -> Gen SlotNo Source #

Control the distribution of how long WaitUntil waits

initialState :: state Source #

The initial state, before any actions have been performed.

precondition :: ModelState state -> Action state -> Bool Source #

The precondition function decides if a given action is valid in a given state. Typically actions generated by arbitraryAction will satisfy the precondition, but if they don't they will be discarded and another action will be generated. More importantly, the preconditions are used when shrinking (see shrinkAction) to ensure that shrunk test cases still make sense.

If an explicit action in a DL scenario violates the precondition an error is raised.

nextReactiveState :: SlotNo -> Spec state () Source #

nextReactiveState is run every time the model waits for a slot to be reached. This can be used to model reactive components of off-chain code.

nextState :: Action state -> Spec state () Source #

This is where the model logic is defined. Given an action, nextState specifies the effects running that action has on the model state. It runs in the Spec monad, which is a state monad over the ModelState.

shrinkAction :: ModelState state -> Action state -> [Action state] Source #

When a test involving random sequences of actions fails, the framework tries to find a minimal failing test case by shrinking the original failure. Action sequences are shrunk by removing individual actions, or by replacing an action by one of the (simpler) actions returned by shrinkAction.

See shrink for more information on shrinking.

restricted :: Action state -> Bool Source #

class (ContractModel state, IsRunnable m) => RunModel state m where Source #

Minimal complete definition

perform

Methods

perform :: ModelState state -> Action state -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> RunMonad 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.

monitoring :: (ModelState state, ModelState state) -> Action state -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> SymIndex -> 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.

class (DefaultRealized m, HasChainIndex m, Monad m) => IsRunnable m where Source #

Methods

awaitSlot :: SlotNo -> m () Source #

Instances

Instances details
IsRunnable m => IsRunnable (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

awaitSlot :: SlotNo -> RunMonad m () Source #

(DefaultRealized m, IsRunnable m) => IsRunnable (ReaderT r m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

awaitSlot :: SlotNo -> ReaderT r m () Source #

(DefaultRealized m, IsRunnable m) => IsRunnable (StateT s m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

awaitSlot :: SlotNo -> StateT s m () Source #

(Monoid w, DefaultRealized m, IsRunnable m) => IsRunnable (WriterT w m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

awaitSlot :: SlotNo -> WriterT w m () Source #

type DefaultRealized m = (Realized m SymIndex ~ SymIndex, Realized m () ~ ()) Source #

newtype RunMonad m a Source #

Constructors

RunMonad 

Fields

Instances

Instances details
MonadTrans RunMonad Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

lift :: Monad m => m a -> RunMonad m a

MonadError e m => MonadError e (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

throwError :: e -> RunMonad m a

catchError :: RunMonad m a -> (e -> RunMonad m a) -> RunMonad m a

MonadState s m => MonadState s (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

get :: RunMonad m s

put :: s -> RunMonad m ()

state :: (s -> (a, s)) -> RunMonad m a

Monad m => MonadWriter SymIndex (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

writer :: (a, SymIndex) -> RunMonad m a

tell :: SymIndex -> RunMonad m ()

listen :: RunMonad m a -> RunMonad m (a, SymIndex)

pass :: RunMonad m (a, SymIndex -> SymIndex) -> RunMonad m a

Monad m => Monad (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

(>>=) :: RunMonad m a -> (a -> RunMonad m b) -> RunMonad m b Source #

(>>) :: RunMonad m a -> RunMonad m b -> RunMonad m b Source #

return :: a -> RunMonad m a Source #

Functor m => Functor (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

fmap :: (a -> b) -> RunMonad m a -> RunMonad m b Source #

(<$) :: a -> RunMonad m b -> RunMonad m a Source #

Monad m => MonadFail (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

fail :: String -> RunMonad m a Source #

Applicative m => Applicative (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

pure :: a -> RunMonad m a Source #

(<*>) :: RunMonad m (a -> b) -> RunMonad m a -> RunMonad m b Source #

liftA2 :: (a -> b -> c) -> RunMonad m a -> RunMonad m b -> RunMonad m c Source #

(*>) :: RunMonad m a -> RunMonad m b -> RunMonad m b Source #

(<*) :: RunMonad m a -> RunMonad m b -> RunMonad m a Source #

(Monad m, HasChainIndex m) => HasChainIndex (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

IsRunnable m => IsRunnable (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

awaitSlot :: SlotNo -> RunMonad m () Source #

(IsRunnable m, RunModel state m) => RunModel (ModelState state) (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

perform :: Typeable a => ModelState state -> Action (ModelState state) a -> LookUp (RunMonad m) -> RunMonad m (Realized (RunMonad m) a)

postcondition :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> PostconditionM (RunMonad m) Bool

monitoring :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> Property -> Property

type Realized (RunMonad m) a Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

type Realized (RunMonad m) a = Realized m a

data Actions s Source #

Instances

Instances details
ContractModel state => Show (Actions state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

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

show :: Actions state -> String Source #

showList :: [Actions state] -> ShowS Source #

ContractModel s => Arbitrary (Actions s) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

arbitrary :: Gen (Actions s)

shrink :: Actions s -> [Actions s]

data Act s Source #

Constructors

Bind 

Fields

NoBind 

Fields

ActWaitUntil (Var ()) SlotNo 
ActObservation (Var ()) String (SymbolicSemantics -> ChainState -> Bool) 

Instances

Instances details
ContractModel s => Eq (Act s) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

(==) :: Act s -> Act s -> Bool Source #

(/=) :: Act s -> Act s -> Bool Source #

ContractModel state => Show (Act state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

showsPrec :: Int -> Act state -> ShowS Source #

show :: Act state -> String Source #

showList :: [Act state] -> ShowS Source #

pattern Actions :: [Act s] -> Actions s Source #

ContractAction :: Bool -> Action state -> Action (ModelState state) SymIndex Source #

WaitUntil :: SlotNo -> Action (ModelState state) () Source #

stateAfter :: ContractModel state => Actions state -> ModelState state Source #

runContractModel :: (ContractModel state, RunModel state m, HasChainIndex m) => Actions state -> PropertyM (RunMonad m) (ContractModelResult state) Source #

liftRunMonad :: (forall a. m a -> n a) -> RunMonad m a -> RunMonad n a Source #

contractState :: forall state state. Lens (ModelState state) (ModelState state) state state Source #

Lens for the contract-specific part of the model state.

registerToken :: Monad m => String -> AssetId -> RunMonad m () Source #

registerTxOut :: Monad m => String -> TxOut CtxUTxO Era -> RunMonad m () Source #

registerTxIn :: Monad m => String -> TxIn -> RunMonad m () Source #

Chain index

class HasChainIndex m where Source #

Instances

Instances details
(Monad m, HasChainIndex m) => HasChainIndex (PostconditionM m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

getChainIndex :: PostconditionM m ChainIndex Source #

getChainState :: PostconditionM m ChainState Source #

(Monad m, HasChainIndex m) => HasChainIndex (RunMonad m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

(Monad m, HasChainIndex m) => HasChainIndex (ReaderT r m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.ChainIndex

Methods

getChainIndex :: ReaderT r m ChainIndex Source #

getChainState :: ReaderT r m ChainState Source #

(Monad m, HasChainIndex m) => HasChainIndex (StateT s m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.ChainIndex

Methods

getChainIndex :: StateT s m ChainIndex Source #

getChainState :: StateT s m ChainState Source #

(Monad m, Monoid w, HasChainIndex m) => HasChainIndex (WriterT w m) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.ChainIndex

Methods

getChainIndex :: WriterT w m ChainIndex Source #

getChainState :: WriterT w m ChainState Source #

data ChainState Source #

Constructors

ChainState 

Fields

data TxInState Source #

Constructors

TxInState 

Fields

type Era = BabbageEra Source #

The safe interface to Symbolic

data Symbolic t Source #

Instances

Instances details
TokenLike SymToken Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Eq (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

(==) :: Symbolic t -> Symbolic t -> Bool Source #

(/=) :: Symbolic t -> Symbolic t -> Bool Source #

Ord (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

HasSymbolicRep t => Show (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

HasVariables (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

getAllVariables :: Symbolic t -> Set (Any Var)

HasSymbolicRep t => HasSymbolics (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

type SymToken = Symbolic AssetId Source #

A symbolic token is a token that is only available at runtime

type SymTxOut = Symbolic (TxOut CtxUTxO Era) Source #

A SymTxOut is a `TxOut CtxUTxO Era` that is only available at runtime

type SymTxIn = Symbolic TxIn Source #

A SymTxIn is a TxIn that is only available at runtime

data SymValue Source #

A symbolic value is a combination of a real value and a value associating symbolic tokens with an amount

Instances

Instances details
Eq SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Show SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Generic SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep SymValue :: Type -> Type Source #

Semigroup SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Monoid SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Pretty SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

SymValueLike SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

type Rep SymValue = D1 ('MetaData "SymValue" "Test.QuickCheck.ContractModel.Internal.Symbolics" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'False) (C1 ('MetaCons "SymValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "symValMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map SymToken Quantity)) :*: S1 ('MetaSel ('Just "actualValPart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

symIsZero :: SymValue -> Bool Source #

Check if a symbolic value is zero

symLeq :: SymValue -> SymValue -> Bool Source #

Check if one symbolic value is less than or equal to another

toValue :: (SymToken -> AssetId) -> SymValue -> Value Source #

Using a semantics function for symbolic tokens, convert a SymValue to a Value

toSymVal :: (AssetId -> Maybe SymToken) -> Value -> SymValue Source #

Invert a sym token mapping to turn a Value into a SymValue, useful for error reporting

class SymValueLike v where Source #

Methods

toSymValue :: v -> SymValue Source #

Instances

Instances details
SymValueLike Value Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

toSymValue :: Value -> SymValue Source #

SymValueLike SymValue Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

class TokenLike t where Source #

Methods

symAssetIdValueOf :: SymValue -> t -> Quantity Source #

Get the value of a specific token in a SymValue

symAssetIdValue :: t -> Quantity -> SymValue Source #

Convert a token and an amount to a SymValue

Instances

Instances details
TokenLike AssetId Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symAssetIdValueOf :: SymValue -> AssetId -> Quantity Source #

symAssetIdValue :: AssetId -> Quantity -> SymValue Source #

TokenLike SymToken Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

class HasSymbolics a where Source #

Minimal complete definition

Nothing

Instances

Instances details
HasSymbolics Char Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolics Int Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolics Integer Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

(Generic a, GenericHasSymbolics (Rep a)) => HasSymbolics a Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolics Quantity Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolics Value Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolics (BaseType a) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

(HasSymbolics k, HasSymbolics v) => HasSymbolics (Map k v) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

HasSymbolicRep t => HasSymbolics (Symbolic t) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

class HasSymbolicRep t Source #

Minimal complete definition

symIndexL, symPrefix

Instances

Instances details
HasSymbolicRep TxIn Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f TxIn) Source #

symPrefix :: String Source #

HasSymbolicRep AssetId Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f AssetId) Source #

symPrefix :: String Source #

HasSymbolicRep (TxOut CtxUTxO Era) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symIndexL :: forall (f :: Type -> Type). Lens' (SymIndexF f) (f (TxOut CtxUTxO Era)) Source #

symPrefix :: String Source #

Properties

asserts :: ModelState state -> Property Source #

Dynamic logic

The safe interface to Spec

data ModelState state Source #

The ModelState models the state of the blockchain. It contains,

Instances

Instances details
Functor ModelState Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

fmap :: (a -> b) -> ModelState a -> ModelState b Source #

(<$) :: a -> ModelState b -> ModelState a Source #

(ContractModel state, Typeable a) => ActionLike state (Action (ModelState state) a) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

Methods

action :: Action (ModelState state) a -> DL state () Source #

Show state => Show (ModelState state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

showsPrec :: Int -> ModelState state -> ShowS Source #

show :: ModelState state -> String Source #

showList :: [ModelState state] -> ShowS Source #

Generic (ModelState state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type Rep (ModelState state) :: Type -> Type Source #

Methods

from :: ModelState state -> Rep (ModelState state) x Source #

to :: Rep (ModelState state) x -> ModelState state Source #

ContractModel state => StateModel (ModelState state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Associated Types

data Action (ModelState state) a

Methods

actionName :: Action (ModelState state) a -> String

arbitraryAction :: VarContext -> ModelState state -> Gen (Any (Action (ModelState state)))

shrinkAction :: Typeable a => VarContext -> ModelState state -> Action (ModelState state) a -> [Any (Action (ModelState state))]

initialState :: ModelState state

nextState :: Typeable a => ModelState state -> Action (ModelState state) a -> Var a -> ModelState state

precondition :: ModelState state -> Action (ModelState state) a -> Bool

GetModelState (DL state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

Associated Types

type StateType (DL state) Source #

Methods

getModelState :: DL state (ModelState (StateType (DL state))) Source #

ContractModel s => DynLogicModel (ModelState s) 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

Methods

restricted :: Action (ModelState s) a -> Bool

(IsRunnable m, RunModel state m) => RunModel (ModelState state) (RunMonad m) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

perform :: Typeable a => ModelState state -> Action (ModelState state) a -> LookUp (RunMonad m) -> RunMonad m (Realized (RunMonad m) a)

postcondition :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> PostconditionM (RunMonad m) Bool

monitoring :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> Property -> Property

ContractModel state => Eq (Action (ModelState state) a) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

(==) :: Action (ModelState state) a -> Action (ModelState state) a -> Bool Source #

(/=) :: Action (ModelState state) a -> Action (ModelState state) a -> Bool Source #

ContractModel state => Show (Action (ModelState state) a) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

showsPrec :: Int -> Action (ModelState state) a -> ShowS Source #

show :: Action (ModelState state) a -> String Source #

showList :: [Action (ModelState state) a] -> ShowS Source #

HasVariables (Action state) => HasVariables (Action (ModelState state) a) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllVariables :: Action (ModelState state) a -> Set (Any Var)

type Rep (ModelState state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

type Rep (ModelState state) = D1 ('MetaData "ModelState" "Test.QuickCheck.ContractModel.Internal.Spec" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'False) (C1 ('MetaCons "ModelState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_currentSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "_balanceChanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (AddressInEra Era) SymValue)) :*: S1 ('MetaSel ('Just "_minted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymValue))) :*: ((S1 ('MetaSel ('Just "_symbolics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymCollectionIndex) :*: S1 ('MetaSel ('Just "_assertions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Bool)])) :*: (S1 ('MetaSel ('Just "_assertionsOk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_contractState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 state)))))
data Action (ModelState state) a 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

data Action (ModelState state) a where
type StateType (DL state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

type StateType (DL state) = state

newtype Spec state a Source #

The Spec monad is a state monad over the ModelState with reader and writer components to keep track of newly created symbolic tokens. It is used exclusively by the nextState function to model the effects of an action on the blockchain.

Constructors

Spec 

Fields

Instances

Instances details
MonadState state (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

get :: Spec state state

put :: state -> Spec state ()

state :: (state -> (a, state)) -> Spec state a

Monad (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

(>>=) :: Spec state a -> (a -> Spec state b) -> Spec state b Source #

(>>) :: Spec state a -> Spec state b -> Spec state b Source #

return :: a -> Spec state a Source #

Functor (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

fmap :: (a -> b) -> Spec state a -> Spec state b Source #

(<$) :: a -> Spec state b -> Spec state a Source #

Applicative (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

pure :: a -> Spec state a Source #

(<*>) :: Spec state (a -> b) -> Spec state a -> Spec state b Source #

liftA2 :: (a -> b -> c) -> Spec state a -> Spec state b -> Spec state c Source #

(*>) :: Spec state a -> Spec state b -> Spec state b Source #

(<*) :: Spec state a -> Spec state b -> Spec state a Source #

GetModelState (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type StateType (Spec state) Source #

Methods

getModelState :: Spec state (ModelState (StateType (Spec state))) Source #

type StateType (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

type StateType (Spec state) = state

class Monad m => GetModelState m where Source #

Monads with read access to the model state: the Spec monad used in nextState, and the DL monad used to construct test scenarios.

Associated Types

type StateType m :: * Source #

The contract state type of the monad. For both Spec and DL this is simply the state parameter of the respective monad.

Methods

getModelState :: m (ModelState (StateType m)) Source #

Get the current model state.

Instances

Instances details
GetModelState (Spec state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type StateType (Spec state) Source #

Methods

getModelState :: Spec state (ModelState (StateType (Spec state))) Source #

GetModelState (DL state) Source # 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

Associated Types

type StateType (DL state) Source #

Methods

getModelState :: DL state (ModelState (StateType (DL state))) Source #

runSpec :: Spec state () -> Var SymIndex -> ModelState state -> ModelState state Source #

currentSlot :: Getter (ModelState state) SlotNo Source #

Get the current slot.

Spec monad update functions: wait and waitUntil.

balanceChanges :: Getter (ModelState state) (Map (AddressInEra Era) SymValue) Source #

Get the current wallet balance changes. These are delta balances, so they start out at zero and can be negative. The absolute balances used by the emulator can be set in the CheckOptions argument to propRunActionsWithOptions.

Spec monad update functions: withdraw, deposit, transfer.

balanceChange :: Ord (AddressInEra Era) => AddressInEra Era -> Getter (ModelState state) SymValue Source #

Get the current balance change for a wallet. This is the delta balance, so it starts out at zero and can be negative. The absolute balance used by the emulator can be set in the CheckOptions argument to propRunActionsWithOptions.

Spec monad update functions: withdraw, deposit, transfer.

minted :: Getter (ModelState state) SymValue Source #

Get the amount of tokens minted so far. This is used to compute lockedValue.

Spec monad update functions: mint and burn.

lockedValue :: ModelState s -> SymValue Source #

How much value is currently locked by contracts. This computed by subtracting the wallet balances from the minted value.

getContractState :: GetModelState m => m (StateType m) Source #

Get the contract state part of the model state.

askModelState :: GetModelState m => (ModelState (StateType m) -> a) -> m a Source #

Get a component of the model state.

askContractState :: GetModelState m => (StateType m -> a) -> m a Source #

Get a component of the contract state.

viewModelState :: GetModelState m => Getting a (ModelState (StateType m)) a -> m a Source #

Get a component of the model state using a lens.

viewContractState :: GetModelState m => Getting a (StateType m) a -> m a Source #

Get a component of the contract state using a lens.

createSymbolic :: forall t state. HasSymbolicRep t => String -> Spec state (Symbolic t) Source #

createToken :: String -> Spec state SymToken Source #

Create a new symbolic token in nextState - must have a corresponding registerToken call in perform

createTxOut :: String -> Spec state SymTxOut Source #

Create a new symbolic TxOut in nextState - must have a corresponding registerTxOut call in perform

createTxIn :: String -> Spec state SymTxIn Source #

Create a new symbolic TxIn in nextState - must have a corresponding registerTxIn call in perform

mint :: SymValueLike v => v -> Spec state () Source #

Mint tokens. Minted tokens start out as lockedValue (i.e. owned by the contract) and can be transferred to wallets using deposit.

burn :: SymValueLike v => v -> Spec state () Source #

Burn tokens. Equivalent to mint . inv.

deposit :: SymValueLike v => AddressInEra Era -> v -> Spec state () Source #

Add tokens to the balanceChange of an address. The added tokens are subtracted from the lockedValue of tokens held by contracts.

withdraw :: SymValueLike v => AddressInEra Era -> v -> Spec state () Source #

Withdraw tokens from an address. The withdrawn tokens are added to the lockedValue of tokens held by contracts.

transfer Source #

Arguments

:: SymValueLike v 
=> AddressInEra Era

Transfer from this address

-> AddressInEra Era

to this address

-> v

this much value

-> Spec state () 

Transfer tokens between wallets, updating their balances.

waitUntil :: ContractModel state => SlotNo -> Spec state () Source #

Wait until the given slot. Has no effect if currentSlot is greater than the given slot.

wait :: ContractModel state => Integer -> Spec state () Source #

Wait the given number of slots. Updates the currentSlot of the model state.

assertSpec :: String -> Bool -> Spec state () Source #

Assert that a particular predicate holds at a point in the specification

coerceSpec :: forall s s' a. Coercible s s' => Spec s a -> Spec s' a Source #

Internals