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

Test.Cleveland.Internal.Actions.Originate

Description

Machinery for the variadic originate function.

Synopsis

Documentation

data Large Source #

Mark a contract that doesn't fit into the origination size limit. This will execute multiple origination steps.

Such origination cannot be batched (it simply may not fit).

Constructors

Large 

Instances

Instances details
(OFConstraints ct 'PropLarge props r, GetLarge props ~ 'NotLarge) => OriginateFunc ct props (Large -> r) Source #

Set large origination.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

data Prop Source #

Enum for props we track duplicates of.

class (MonadOpsInternal m, forall ct props a. TerminatingOFConstraints ct props m a => OriginateFunc ct props (m a)) => MonadOriginate m Source #

A convenient synonym class to require the terminating instance for a given monad without leaking too much implementation detail.

Instances

Instances details
(MonadOpsInternal m, forall ct (props :: [Prop]) a. TerminatingOFConstraints ct props m a => OriginateFunc ct props (m a)) => MonadOriginate m Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

class ContractClass contract where Source #

Type class that abstracts different contract types for the purpose of origination.

Associated Types

type ContractOriginateType contract :: OriginationType Source #

Instances

Instances details
ContractClass Contract Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

Associated Types

type ContractOriginateType Contract :: OriginationType Source #

(NiceStorage st, NiceViewsDescriptor vd, NiceParameter cp) => ContractClass (TypedContract cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

Associated Types

type ContractOriginateType (TypedContract cp st vd) :: OriginationType Source #

ContractClass (Contract cp st vd) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

Associated Types

type ContractOriginateType (Contract cp st vd) :: OriginationType Source #

Methods

initialStorageAndContract :: ContractStorage (Contract cp st vd) -> Contract cp st vd -> ODContractAndStorage (ContractOriginateType (Contract cp st vd)) Source #

class OriginateFunc contract (props :: [Prop]) r where Source #

The class implementing a guarded "printf trick" for the originate function.

If you see GHC asking for this constraint, you most likely need to add MonadOriginate constraint on the return monad instead.

Instances

Instances details
TerminatingOFConstraints ct props ClevelandOpsBatch a => OriginateFunc ct props (ClevelandOpsBatch a) Source #

The terminating case for batched transfer.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

(OFConstraints ct 'PropLarge props r, GetLarge props ~ 'NotLarge) => OriginateFunc ct props (Large -> r) Source #

Set large origination.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

OFConstraints ct 'PropBalance props r => OriginateFunc ct props (Mutez -> r) Source #

Set balance.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

OFConstraints ct 'PropDelegate props r => OriginateFunc ct props (KeyHash -> r) Source #

Set delegate.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

Methods

originate'r :: OriginateData (ContractOriginateType ct) (GetLarge props) -> KeyHash -> r Source #

(TypeError (('Text "Incorrect argument for the 'originate' function: " ':<>: 'ShowType x) ':$$: 'Text "If in doubt, try adding a type annotation.") :: Constraint, Bottom) => OriginateFunc ct props (x -> r) Source #

Catchall incoherent instance to report argument errors.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

TerminatingOFConstraints ct props (ReaderT cap base) a => OriginateFunc ct props (ReaderT cap base a) Source #

The terminating case for Cleveland monads.

Instance details

Defined in Test.Cleveland.Internal.Actions.Originate

class MonadOpsInternal m => Originator large m where Source #

Class doing actual origination.

type family ContractStorage' contract where ... Source #

Equations

ContractStorage' 'OTUntyped = Value 
ContractStorage' ('OTTypedMorley _ st _) = st 
ContractStorage' ('OTTypedLorentz _ st _) = st 

type family GetLarge a where ... Source #

Convert a list of props into LargeOrigination.

Equations

GetLarge ('PropLarge ': _) = 'IsLarge 
GetLarge (_ ': xs) = GetLarge xs 
GetLarge '[] = 'NotLarge 

type family PropName a where ... Source #

Pretty prop name.

Equations

PropName 'PropBalance = "Balance" 
PropName 'PropDelegate = "Delegate" 
PropName 'PropLarge = "Large" 

type family CheckDupProp name props where ... Source #

Type family raising a type error if element is in list. Used to improve error reporting for OriginateFunc instances with equality constraints.

Equations

CheckDupProp name (name ': _) = TypeError ('Text (PropName name) ':<>: 'Text " is specified more than once.") 
CheckDupProp name (_ ': xs) = CheckDupProp name xs 
CheckDupProp _ '[] = () 

type OFConstraints ct prop props r = (OriginateFunc ct (prop ': props) r, CheckDupProp prop props) Source #

Convenience synonym for constraints used in OriginateFunc instances.

type TerminatingOFConstraints ct props m a = (Originator (GetLarge props) m, a ~ OriginationResult (ContractOriginateType ct)) Source #

Common constraints for terminating OriginateFunc cases.

originate :: forall contract r. (HasCallStack, ContractClass contract, OriginateFunc contract '[] r) => ContractAlias -> ContractStorage contract -> contract -> r Source #

Originate a new contract with given data.

Can accept untypted or Lorentz contracts as-is. With typed Michelson contracts, you need to wrap the contract in TypedContract specifying its Haskell-land parameter, storage types and view descriptors, e.g.

originate "typed contract" defaultStorage $ TypedContract @Param @Storage @() michelsonContract

Storage type can be auto-deduced in most cases, so you can skip it with @_.

After the mandatory arguments, you can add Large or a Mutez value, e.g. by using tz quasi-quoter:

originate "contract" initialStorage contract Large
originate "contract" initialStorage contract [tz|123micro|]
originate "contract" initialStorage contract [tz|123micro|] Large

The order is arbitrary, but each can be specified at most once.

originateFn :: (HasCallStack, Originator large m) => OriginateData ot large -> m (OriginationResult ot) Source #

Low-level polymorphic origination function. It takes arbitrary OriginateData, and, depending on whether the data is typed or not, returns respectively a ContractHandle, or a ContractAddress, in a suitable monad (or an applicative functor in case of batched originations).