cleveland-0.3.1: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cleveland.Internal.Pure

Description

Integration with integrational testing engine (pun intended).

Synopsis

Documentation

newtype PureM a Source #

Constructors

PureM 

Instances

Instances details
MonadFail PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

fail :: String -> PureM a #

MonadIO PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

liftIO :: IO a -> PureM a #

Applicative PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

pure :: a -> PureM a #

(<*>) :: PureM (a -> b) -> PureM a -> PureM b #

liftA2 :: (a -> b -> c) -> PureM a -> PureM b -> PureM c #

(*>) :: PureM a -> PureM b -> PureM b #

(<*) :: PureM a -> PureM b -> PureM a #

Functor PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

fmap :: (a -> b) -> PureM a -> PureM b #

(<$) :: a -> PureM b -> PureM a #

Monad PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

(>>=) :: PureM a -> (a -> PureM b) -> PureM b #

(>>) :: PureM a -> PureM b -> PureM b #

return :: a -> PureM a #

MonadScenario PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Scenario

MonadCatch PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

catch :: Exception e => PureM a -> (e -> PureM a) -> PureM a #

MonadThrow PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

throwM :: Exception e => e -> PureM a #

MonadState PureState PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

get :: PureM PureState #

put :: PureState -> PureM () #

state :: (PureState -> (a, PureState)) -> PureM a #

MonadWriter LogsInfo PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

Methods

writer :: (a, LogsInfo) -> PureM a #

tell :: LogsInfo -> PureM () #

listen :: PureM a -> PureM (a, LogsInfo) #

pass :: PureM (a, LogsInfo -> LogsInfo) -> PureM a #

MonadReader (IORef PureState) PureM Source # 
Instance details

Defined in Test.Cleveland.Internal.Pure

doTransfer :: (ParameterScope (ToT v), IsoValue v, ToL1Address addr) => ImplicitAddress -> addr -> Mutez -> EpName -> v -> PureM [ContractEvent] Source #

findBigMapByIdMaybe :: forall k v. (SingI v, SingI k) => Natural -> MaybeT PureM (Value ('TBigMap k v)) Source #

Traverse storage values of all contracts and looks for a big_map with the given ID.

getBalance :: L1AddressKind kind => KindedAddress kind -> PureM Mutez Source #

getStorageImpl :: forall st addr. ToStorageType st addr => addr -> PureM st Source #

addressState :: KindedAddress kind -> PureM (AddressStateFam kind) Source #

resolveLens :: (MonadState PureState m, At x) => LensLike' (Const (Maybe (IxValue x))) GState x -> (Index x -> m b) -> (Index x -> IxValue x -> b) -> Index x -> m b Source #

resolveAlias :: (At x, Index x ~ Alias kind, IxValue x ~ KindedAddress kind) => LensLike' (Const (Maybe (IxValue x))) GState x -> Alias kind -> PureM (AddressWithAlias kind) Source #

resolveAddress :: x ~ Bimap (Alias kind) (KindedAddress kind) => LensLike' (Const (Maybe (Index x))) GState x -> KindedAddress kind -> PureM (AddressWithAlias kind) Source #

unknownAlias :: Alias kind -> PureM whatever Source #

failure :: forall a. Builder -> PureM a Source #

transfer :: (ParameterScope (ToT epArg), IsoValue epArg, ToAddress addr) => ("from" :! ImplicitAddress) -> ("to" :! addr) -> Mutez -> EpName -> epArg -> PureM [EmitOperation] Source #

originate :: OriginateData oty large -> PureM ContractAddress Source #

Originate a contract with given initial storage and balance. Its address is returned.

throwEE :: ExecutorError -> PureM a Source #

registerInterpretation :: ExecutorM a -> PureM a Source #

Runs a set of operations and updates the engine's state.

interpret :: ExecutorM a -> PureM (Either ExecutorError (ExecutorRes, a)) Source #

Interpret an action and return the result _without_ updating the engine's state.