morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Test

Contents

Synopsis

Importing a contract

specWithContract :: (Each [Typeable, SingI] [cp, st], HasCallStack) => FilePath -> ((Contract, Contract cp st) -> Spec) -> Spec Source #

Import contract and use it in the spec. Both versions of contract are passed to the callback function (untyped and typed).

If contract's import failed, a spec with single failing expectation will be generated (so tests will run unexceptionally, but a failing result will notify about problem).

specWithTypedContract :: (Each [Typeable, SingI] [cp, st], HasCallStack) => FilePath -> (Contract cp st -> Spec) -> Spec Source #

A version of specWithContract which passes only the typed representation of the contract.

Unit testing

type ContractPropValidator st prop = ContractReturn st -> prop Source #

Type for contract execution validation.

It's a function which is supplied with contract execution output (failure or new storage with operation list).

Function returns a property which type is designated by type variable prop and might be Property or Expectation or anything else relevant.

contractProp :: (IsoValue param, IsoValue storage, ToT param ~ cp, ToT storage ~ st) => Contract cp st -> ContractPropValidator st prop -> ContractEnv -> param -> storage -> prop Source #

Contract's property tester against given input. Takes contract environment, initial storage and parameter, interprets contract on this input and invokes validation function.

contractPropVal :: Contract cp st -> ContractPropValidator st prop -> ContractEnv -> Value cp -> Value st -> prop Source #

Version of contractProp which takes Val as arguments instead of regular Haskell values.

contractRepeatedProp :: (IsoValue param, IsoValue storage, ToT param ~ cp, ToT storage ~ st) => Contract cp st -> ContractPropValidator st prop -> ContractEnv -> [param] -> storage -> prop Source #

Integrational testing

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 ValidationError) Source #

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

integrationalTestExpectation :: 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 :: (SingI (ToT cp), SingI (ToT st), HasNoOp (ToT st), IsoValue st) => Contract cp st -> Text -> st -> Mutez -> IntegrationalScenarioM (ContractAddr cp) Source #

Like originate, but for Lorentz contracts.

lOriginateEmpty :: (SingI (ToT cp), SingI (ToT st), HasNoOp (ToT st), IsoValue st, Default st) => Contract cp st -> Text -> IntegrationalScenarioM (ContractAddr cp) Source #

Originate a contract with empty balance and default storage.

lTransfer :: (SingI (ToT cp), HasNoOp (ToT cp), IsoValue cp) => ("from" :! Address) -> ("to" :! ContractAddr cp) -> Mutez -> cp -> IntegrationalScenarioM () Source #

Similar to transfer, for Lorentz values.

lCall :: (SingI (ToT cp), HasNoOp (ToT cp), IsoValue cp) => ContractAddr cp -> cp -> IntegrationalScenarioM () Source #

Call a contract without caring about source address and money.

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.

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).

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.

lExpectStorageUpdate :: (IsoValue st, Each [Typeable, SingI, HasNoOp] '[ToT st], HasCallStack) => ContractAddr cp -> (st -> Either ValidationError ()) -> SuccessValidator Source #

Similar to expectStorageUpdate, for Lorentz values.

lExpectBalance :: ContractAddr cp -> Mutez -> SuccessValidator Source #

Like expectBalance, for Lorentz values.

lExpectStorageConst :: (IsoValue st, Each '[SingI, HasNoOp] '[ToT st]) => ContractAddr cp -> st -> SuccessValidator Source #

Similar to expectStorageConst, for Lorentz values.

lExpectMichelsonFailed :: (MichelsonFailed -> Bool) -> ContractAddr cp -> 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.

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

Expect contract to fail with given LorentzUserError error.

lExpectConsumerStorage :: (st ~ [cp], IsoValue st, Each [Typeable, SingI, HasNoOp] '[ToT st]) => ContractAddr cp -> (st -> Either ValidationError ()) -> SuccessValidator Source #

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

lExpectViewConsumerStorage :: (st ~ [cp], cp ~ (arg, Maybe res), Eq res, Buildable res, IsoValue st, Each [Typeable, SingI, HasNoOp] '[ToT st]) => ContractAddr cp -> [res] -> 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.

Various

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.

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 !!

General utilities

failedProp :: Text -> Property Source #

A Property that always failes with given message.

succeededProp :: Property Source #

A Property that always succeeds.

qcIsLeft :: Show b => Either a b -> Property Source #

The Property holds on `Left a`.

qcIsRight :: Show a => Either a b -> Property Source #

The Property holds on `Right b`.

Dummy values

dummyContractEnv :: ContractEnv Source #

Dummy ContractEnv with some reasonable hardcoded values. You can override values you are interested in using record update syntax.

Arbitrary data

minTimestamp :: Timestamp Source #

Minimal (earliest) timestamp used for Arbitrary (CValue 'CTimestamp)

maxTimestamp :: Timestamp Source #

Maximal (latest) timestamp used for Arbitrary (CValue 'CTimestamp)

midTimestamp :: Timestamp Source #

Median of minTimestamp and maxTimestamp. Useful for testing (exactly half of generated dates will be before and after this date).