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

Test.Cleveland.Lorentz

Synopsis

Importing a contract

importContract :: forall cp st vd. (NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd, DemoteViewsDescriptor vd) => FilePath -> IO (Contract cp st vd) Source #

Import contract from a given FilePath.

In this and similar functions, parameter and storage types must exactly match the ones in the contract, while for views this is not necessary. Only make sure that all views beyond vd type are present in the contract; () always works as views descriptor of the contract.

embedContract :: forall cp st vd. (NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd, DemoteViewsDescriptor vd) => FilePath -> Code Q (Contract cp st vd) Source #

Import a contract at compile time assuming its expected type is known.

Use it like:

myContract :: Contract Parameter Storage
myContract = $$(embedContract "my_contract.tz")

or

let myContract = $$(embedContract @Parameter @Storage "my_contract.tz")

See also the note in Test.Cleveland.Lorentz.Import

embedContractM :: forall cp st vd. (NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd, DemoteViewsDescriptor vd) => IO FilePath -> Code Q (Contract cp st vd) Source #

Version of embedContract that accepts a filepath constructor in IO.

Useful when the path should depend on environmental variables or other user input.

See also the note in Test.Cleveland.Lorentz.Import

Importing a value

importValue :: forall a. IsoValue a => FilePath -> IO a Source #

Import a value from a given FilePath

embedValue :: forall a. IsoValue a => FilePath -> Code Q a Source #

Import a value from a given FilePath at compile time and embed it as a value using Template Haskell, f. ex.

let someAddress = $$(embedValue @Address "/path/to/addressFile.tz")

See also the note in Test.Cleveland.Lorentz.Import

embedValueM :: forall a. IsoValue a => IO FilePath -> Code Q a Source #

A variant of embedValue that accepts FilePath in IO.

Can be useful when FilePath depends on the environment.

See also the note in Test.Cleveland.Lorentz.Import

Unit testing

testContractCoversEntrypointsT :: forall exp. TestName -> ContractEPTypeTest exp Source #

Expect the contract to cover or exactly match with the entrypoints given in spec passed as the first type argument. Checks both the contract type and the contract itself (when represented as an untyped Michelson contract).

testContractMatchesEntrypointsT :: forall exp. TestName -> ContractEPTypeTest exp Source #

Expect the contract to cover or exactly match with the entrypoints given in spec passed as the first type argument. Checks both the contract type and the contract itself (when represented as an untyped Michelson contract).

testContractCoversEntrypoints :: NiceParameterFull contractEps => TestName -> ContractEPTest contractEps st vd Source #

Expect the contract to cover or exactly match with the entrypoints given in spec passed as a Map of names to types. Checks both the contract type and the contract itself (when represented as an untyped Michelson contract).

testContractMatchesEntrypoints :: NiceParameterFull contractEps => TestName -> ContractEPTest contractEps st vd Source #

Expect the contract to cover or exactly match with the entrypoints given in spec passed as a Map of names to types. Checks both the contract type and the contract itself (when represented as an untyped Michelson contract).

Basic types

data ContractHandle (cp :: Type) (st :: Type) (vd :: Type) Source #

Handle to a contract.

This is what you get when originating a contract and that allows further operations with the contract within the test framework.

Note that this is part of the testing framework and exists solely in Haskell world, so it has no IsoValue and related instances and cannot be used in Lorentz code.

Constructors

(NiceParameter cp, NiceStorage st, NiceViewsDescriptor vd) => ContractHandle 

Instances

Instances details
(cp' ~ cp, vd ~ vd') => ToTAddress cp' vd' (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toTAddress :: ContractHandle cp st vd -> TAddress cp' vd'

st ~ st' => ToStorageType st' (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

ToContractRef arg (TAddress cp vd) => ToContractRef arg (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toContractRef :: ContractHandle cp st vd -> ContractRef arg

Show (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

showsPrec :: Int -> ContractHandle cp st vd -> ShowS #

show :: ContractHandle cp st vd -> String #

showList :: [ContractHandle cp st vd] -> ShowS #

ToContractAddress (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

ToL1Address (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1Address :: ContractHandle cp st vd -> L1Address Source #

Buildable (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

build :: ContractHandle cp st vd -> Builder #

ToAddress (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toAddress :: ContractHandle cp st vd -> Address #

chNiceParameterEvi :: forall param st vd. ContractHandle param st vd -> Dict (ParameterScope $ ToT st) Source #

Extract the evidence in typed Michelson that the parameter type is valid for such scope.

chNiceStorageEvi :: forall param st vd. ContractHandle param st vd -> Dict (StorageScope $ ToT st) Source #

Extract the evidence in typed Michelson that the storage type is valid for such scope.

class ToL1Address addr where Source #

Methods

toL1Address :: addr -> L1Address Source #

Instances

Instances details
ToL1Address L1Address Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1Address :: L1Address -> L1Address Source #

L1AddressKind kind => ToL1Address (KindedAddress kind) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1Address :: KindedAddress kind -> L1Address Source #

ToL1Address (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1Address :: ContractHandle cp st vd -> L1Address Source #

ToL1Address (L1TAddress cp vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1Address :: L1TAddress cp vd -> L1Address Source #

class (ToTAddress cp vd addr, ToL1Address addr) => ToL1TAddress cp vd addr where Source #

Counterpart of ToTAddress that converts to L1TAddress rather than TAddress.

Methods

toL1TAddress :: addr -> L1TAddress cp vd Source #

Instances

Instances details
(ToTAddress cp vd addr, ToL1Address addr) => ToL1TAddress cp vd addr Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Methods

toL1TAddress :: addr -> L1TAddress cp vd Source #

class ToContractAddress addr => ToStorageType st addr where Source #

Declares that addr points to an entity with a storage.

addr may fix storage type or may not - in the latter case the caller has to specify the storage type explicitly via type annotation.

Methods

pickNiceStorage :: addr -> Dict (NiceStorage st) Source #

Pick proof of that storage type is valid.

Instances

Instances details
NiceStorage st => ToStorageType st ContractAddress Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

st ~ st' => ToStorageType st' (ContractHandle cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Lorentz.Types

Conversions

toAddress :: ToAddress a => a -> Address #

Autodoc testing

runDocTests :: (ContainsDoc code, HasCallStack) => [DocTest] -> code -> [TestTree] Source #

Finalize test suites.

testLorentzDoc :: [DocTest] Source #

Tests all properties.

excludeDocTests :: [DocTest] -> [DocTest] -> [DocTest] Source #

Calling excludeDocTests tests toExclude returns all test suites from tests which are not present in toExclude.

General utilities

failedTest :: (HasCallStack, MonadTest m) => Text -> m () Source #

A Property that always fails with given message.

succeededTest :: MonadTest m => m () Source #

A Property that always succeeds.

eitherIsLeft :: (Show b, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Left a`.

eitherIsRight :: (Show a, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Right b`.

meanTimeUpperBoundProp :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to weak head normal form is under the given amount of time.

This test fails if the benchmark takes longer than 30 seconds to run.

meanTimeUpperBoundPropNF :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack, NFData b) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to normal form is under the given amount of time.

This test aborts and fails if the benchmark takes longer than 120 seconds to run.

Re-exports

These functions from Time are re-exported here to make it convenient to call meanTimeUpperBoundProp and meanTimeUpperBoundPropNF.

mcs :: RatioNat -> Time Microsecond #

Creates Microsecond from given Natural.

>>> mcs 42
42mcs

ms :: RatioNat -> Time Millisecond #

Creates Millisecond from given Natural.

>>> ms 42
42ms

sec :: RatioNat -> Time Second #

Creates Second from given Natural.

>>> sec 42
42s

minute :: RatioNat -> Time Minute #

Creates Minute from given Natural.

>>> minute 42
42m

Special contracts for testing

contractConsumer :: (NiceParameterFull cp, NiceStorageFull cp) => Contract cp [cp] () Source #

Remembers parameters it was called with, last goes first.