morley-0.5.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Test.Integrational

Contents

Description

Mirrors Integrational module in a Lorentz way.

Synopsis

Re-exports

data TxData Source #

Data associated with a particular transaction.

Constructors

TxData 
Instances
Eq TxData Source # 
Instance details

Defined in Michelson.Runtime.TxData

Methods

(==) :: TxData -> TxData -> Bool #

(/=) :: TxData -> TxData -> Bool #

Show TxData Source # 
Instance details

Defined in Michelson.Runtime.TxData

genesisAddresses :: NonEmpty Address Source #

Initially these addresses have a lot of money.

genesisAddress :: Address Source #

One of genesis addresses.

More genesis addresses which can be used in tests

genesisAddress1 :: Address Source #

More genesis addresses

We know size of genesisAddresses, so it is safe to use !!

genesisAddress2 :: Address Source #

More genesis addresses

We know size of genesisAddresses, so it is safe to use !!

genesisAddress3 :: Address Source #

More genesis addresses

We know size of genesisAddresses, so it is safe to use !!

Testing engine for bare Typed primitives

tOriginate :: (ParameterScope cp, StorageScope st) => Contract cp st -> Text -> Value st -> Mutez -> IntegrationalScenarioM Address Source #

Like originate, but for typed contract and value.

tTransfer :: forall cp. ParameterScope cp => ("from" :! Address) -> ("to" :! Address) -> Mutez -> Value cp -> IntegrationalScenarioM () Source #

Similar to transfer, for typed values.

tExpectStorageConst :: forall st. StorageScope st => Address -> Value st -> SuccessValidator Source #

Similar to expectStorageConst, for typed stuff.

Testing engine

type IntegrationalValidator = Either (InterpreterError -> Bool) SuccessValidator Source #

Validator for integrational testing. If an error is expected, it should be Left with validator for errors. Otherwise it should check final global state and its updates.

type SuccessValidator = InternalState -> GState -> [GStateUpdate] -> Either ValidationError () Source #

Validator for integrational testing that expects successful execution.

type IntegrationalScenarioM = StateT InternalState (Except ScenarioError) Source #

A monad inside which integrational tests can be described using do-notation.

integrationalTestExpectation :: HasCallStack => IntegrationalScenario -> Expectation Source #

Integrational test that executes given operations and validates them using given validator. It can fail using Expectation capability. It starts with initGState and some reasonable dummy values for gas limit and current timestamp. You can update blockchain state by performing some operations.

integrationalTestProperty :: IntegrationalScenario -> Property Source #

Integrational test similar to integrationalTestExpectation. It can fail using Property capability. It can be used with QuickCheck's forAll to make a property-based test with arbitrary data.

lOriginate :: forall cp st. (NiceParameter cp, NiceStorage st) => Contract cp st -> Text -> st -> Mutez -> IntegrationalScenarioM (ContractRef cp) Source #

Like originate, but for Lorentz contracts.

lOriginateEmpty :: (NiceParameter cp, NiceStorage st, Default st) => Contract cp st -> Text -> IntegrationalScenarioM (ContractRef cp) Source #

Originate a contract with empty balance and default storage.

lTransfer :: forall cp contract. (NiceParameter cp, ToContractRef cp contract) => ("from" :! Address) -> ("to" :! contract) -> Mutez -> cp -> IntegrationalScenarioM () Source #

Similar to transfer, for Lorentz values.

lCall :: forall cp contract. (NiceParameter cp, ToContractRef cp contract) => contract -> cp -> IntegrationalScenarioM () Source #

Call a contract without caring about the source address. Transfers 0 mutez.

validate :: IntegrationalValidator -> IntegrationalScenario Source #

Execute all operations that were added to the scenarion since last validate call. If validator fails, the execution will be aborted.

setMaxSteps :: RemainingSteps -> IntegrationalScenarioM () Source #

Make all further interpreter calls (which are triggered by the validate function) use given gas limit.

setNow :: Timestamp -> IntegrationalScenarioM () Source #

Make all further interpreter calls (which are triggered by the validate function) use given timestamp as the current one.

rewindTime :: Integer -> IntegrationalScenarioM () Source #

Increase current time by the given number of seconds.

withSender :: Address -> IntegrationalScenarioM a -> IntegrationalScenarioM a Source #

Pretend that given address initiates all the transfers within the code block (i.e. SENDER instruction will return this address).

setChainId :: ChainId -> IntegrationalScenarioM () Source #

Make all further interpreter calls (which are triggered by the validate function) use given chain id.

branchout :: HasCallStack => [(Text, IntegrationalScenario)] -> IntegrationalScenario Source #

Execute multiple testing scenarios independently, basing them on scenario built till this point.

The following property holds for this function:

pre >> branchout [a, b, c] = branchout [pre >> a, pre >> b, pre >> c] .

In case of property failure in one of the branches no following branch is executed.

Providing empty list of scenarios to this function causes error; we do not require NonEmpty here though for convenience.

(?-) :: Text -> a -> (Text, a) infixr 0 Source #

Make a tuple with name without extra syntactic noise.

offshoot :: Text -> IntegrationalScenario -> IntegrationalScenarioM () Source #

Test given scenario with the state gathered till this moment; if this scenario passes, go on as if it never happened.

Validators

composeValidators :: SuccessValidator -> SuccessValidator -> SuccessValidator Source #

Compose two success validators.

For example:

expectBalance bal addr composeValidators expectStorageUpdateConst addr2 ValueUnit

composeValidatorsList :: [SuccessValidator] -> SuccessValidator Source #

Compose a list of success validators.

expectNoUpdates :: SuccessValidator Source #

Check that there were no updates.

expectNoStorageUpdates :: SuccessValidator Source #

Check that there were no storage updates.

lExpectStorageUpdate :: forall st addr. (NiceStorage st, ToAddress addr, HasCallStack) => addr -> (st -> Either ValidationError ()) -> SuccessValidator Source #

Similar to expectStorageUpdate, for Lorentz values.

lExpectBalance :: ToAddress addr => addr -> Mutez -> SuccessValidator Source #

Like expectBalance, for Lorentz values.

lExpectStorageConst :: forall st addr. (NiceStorage st, ToAddress addr) => addr -> st -> SuccessValidator Source #

Similar to expectStorageConst, for Lorentz values.

Errors

lExpectMichelsonFailed :: forall addr. ToAddress addr => (MichelsonFailed -> Bool) -> addr -> InterpreterError -> Bool Source #

Expect that interpretation of contract with given address ended with [FAILED].

lExpectFailWith :: forall e. (Typeable (ToT e), IsoValue e) => (e -> Bool) -> InterpreterError -> Bool Source #

Expect contract to fail with FAILWITH instruction and provided value to match against the given predicate.

lExpectError :: forall e. IsError e => (e -> Bool) -> InterpreterError -> Bool Source #

Expect contract to fail with given error.

lExpectErrorNumeric :: forall e. IsError e => ErrorTagMap -> (e -> Bool) -> InterpreterError -> Bool Source #

Version of lExpectError for the case when numeric representation of errors is used.

lExpectCustomError :: forall tag arg. (IsError (CustomError tag), arg ~ ErrorArg tag, Eq arg) => Label tag -> arg -> InterpreterError -> Bool Source #

Expect contract to fail with given CustomError.

lExpectCustomErrorNumeric :: forall tag arg. (IsError (CustomError tag), arg ~ ErrorArg tag, Eq arg) => ErrorTagMap -> Label tag -> arg -> InterpreterError -> Bool Source #

Version of lExpectCustomError for the case when numeric representation of errors is used.

lExpectCustomError_ :: forall tag. (IsError (CustomError tag), ErrorArg tag ~ ()) => Label tag -> InterpreterError -> Bool Source #

Specialization of lExpectCustomError for non-arg error case.

lExpectCustomErrorNumeric_ :: forall tag. (IsError (CustomError tag), ErrorArg tag ~ ()) => ErrorTagMap -> Label tag -> InterpreterError -> Bool Source #

Version of lExpectCustomError_ for the case when numeric representation of errors is used.

Consumer

lExpectConsumerStorage :: forall cp st contract. (st ~ [cp], NiceStorage st, ToContractRef cp contract) => contract -> (st -> Either ValidationError ()) -> SuccessValidator Source #

Version of lExpectStorageUpdate specialized to "consumer" contract (see contractConsumer).

lExpectViewConsumerStorage :: (st ~ [cp], Eq cp, Buildable cp, NiceStorage st, ToContractRef cp contract) => contract -> [cp] -> SuccessValidator Source #

Assuming that "consumer" contract receives a value from View, expect this view return value to be the given one.

Despite consumer stores parameters it was called with in reversed order, this function cares about it, so you should provide a list of expected values in the same order in which the corresponding events were happenning.