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

Test.Cleveland.Internal.Actions.Transfer

Description

Machinery for the variadic transfer function.

Synopsis

Documentation

type family FTransferResult emit :: Type where ... Source #

Type family encoding the actual transfer result depending on TransferResult

data TransferResult Source #

Simple flag to track whether we want to return list of emitted events.

data WithContractEvents Source #

transfer flag to signal we want contract events emitted by EMIT returned. Passed in the variadic part of transfer, e.g.

transfer addr [tz|123u|] WithContractEvents $ calling (ep @"Entrypoint") ()

Constructors

WithContractEvents 

Instances

Instances details
(TransferFunc mode 'TransferWithEmits am r, NoDuplicateEmit emit, emit ~ 'TransferIgnoreResult) => TransferFunc mode emit am (WithContractEvents -> r) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

class (forall mod am emit a. (SingI emit, DoTransfer mod, a ~ FTransferResult emit) => TransferFunc mod emit am (m a)) => MonadTransfer m Source #

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

Instances

Instances details
(forall (mod :: TransferMode) (am :: HasAmount) (emit :: TransferResult) a. (SingI emit, DoTransfer mod, a ~ FTransferResult emit) => TransferFunc mod emit am (m a)) => MonadTransfer m Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

type family MatchModes from to :: Constraint where ... Source #

Type family that defines possible mode conversions in TransferFunc. Basically, we don't allow unchecked calls to become checked, and we require that checked calls do not change the parameter type mid-way.

Equations

MatchModes ('Incomplete _) 'Unchecked = () 
MatchModes ('Incomplete ('Checked param1)) ('Checked param2) = param1 ~ param2 
MatchModes ('Incomplete 'Unchecked) _ = TypeError ('Text "Can not use this type of call with an untyped address." :$$: 'Text "Try using 'unsafeCalling' instead.") 
MatchModes _ _ = TypeError ('Text "Call is specified more than once.") 

type family NoDuplicateEmit am :: Constraint where ... Source #

Type family raising a type error on TransferWithEmits argument. Used to improve error reporting for TransferFunc instances with equality constraints.

Equations

NoDuplicateEmit 'TransferWithEmits = TypeError ('Text "WithContractEvents is specified more than once.") 
NoDuplicateEmit 'TransferIgnoreResult = () 

type family NoDuplicateAmount am :: Constraint where ... Source #

Type family raising a type error on HasAmount argument. Used to improve error reporting for TransferFunc instances with equality constraints.

Equations

NoDuplicateAmount 'HasAmount = TypeError ('Text "Amount is specified more than once.") 
NoDuplicateAmount 'HasNoAmount = () 

class TransferFunc (mode :: TransferMode) (emit :: TransferResult) (hasAmount :: HasAmount) r where Source #

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

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

Instances

Instances details
(SingI emit, DoTransfer mode, a ~ FTransferResult emit) => TransferFunc mode emit am (ClevelandOpsBatch a) Source #

The terminating case for batched transfer

Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

(TransferFunc mode 'TransferWithEmits am r, NoDuplicateEmit emit, emit ~ 'TransferIgnoreResult) => TransferFunc mode emit am (WithContractEvents -> r) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

(TransferFunc mode emit 'HasAmount r, NoDuplicateAmount am, am ~ 'HasNoAmount) => TransferFunc mode emit am (Mutez -> r) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

(Bottom, TypeError (('Text "Incorrect argument for the 'transfer' function: " :<>: 'ShowType x) :$$: 'Text "If in doubt, try adding a type annotation.") :: Constraint) => TransferFunc mode emit am (x -> r) Source #

Catchall incoherent instance to report argument errors.

Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

Methods

transfer'r :: GenericTransferData mode -> x -> r Source #

(TransferFunc modeTo emit am r, MatchModes modeFrom modeTo) => TransferFunc modeFrom emit am (GenericCall modeTo -> r) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

Methods

transfer'r :: GenericTransferData modeFrom -> GenericCall modeTo -> r Source #

(SingI emit, DoTransfer mode, HasClevelandCaps cap, base ~ ClevelandBaseMonad cap, a ~ FTransferResult emit) => TransferFunc mode emit am (ReaderT cap base a) Source #

The terminating case for Cleveland monads

Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

Methods

transfer'r :: GenericTransferData mode -> ReaderT cap base a Source #

data HasAmount Source #

Simple flag to track duplicate amount specification.

Constructors

HasAmount 
HasNoAmount 

type family InitialTransferMode addr :: TransferMode where ... Source #

Choose the initial TransferMode based on the type of destination address.

Equations

InitialTransferMode ContractAddress = 'Unchecked 
InitialTransferMode ImplicitAddress = 'Unchecked 
InitialTransferMode L1Address = 'Unchecked 
InitialTransferMode (L1TAddress param _) = 'Checked param 
InitialTransferMode (ContractHandle param _ _) = 'Checked param 
InitialTransferMode Address = TypeError ('Text "'Address' can not be used as the first argument of 'transfer'." :$$: 'Text "Perhaps you meant to use 'L1Address'?") 
InitialTransferMode (TAddress _ _) = TypeError ('Text "'TAddress' can not be used as the first argument of 'transfer'." :$$: 'Text "Perhaps you meant to use 'L1TAddress'?") 
InitialTransferMode x = TypeError (((('Text "Address type '" :<>: 'ShowType x) :<>: 'Text "' is unsupported or ambiguous.") :$$: 'Text "The supported address types are") :$$: 'Text "'ContractAddress', 'ImplicitAddress', 'L1Address', 'L1TAddress', and 'ContractHandle'") 

data GenericTransferData mode Source #

Generic version of TransferData

Constructors

GenericTransferData 

Fields

data GenericCall mode where Source #

Data-kind for call specification.

Constructors

CheckedCall :: (NiceParameter epArg, HasEntrypointArg param epRef epArg) => epRef -> epArg -> GenericCall ('Checked param) 
UncheckedCall :: NiceParameter epArg => EpName -> epArg -> GenericCall 'Unchecked 
UnspecifiedCall :: GenericCall ('Incomplete param) 

Instances

Instances details
(TransferFunc modeTo emit am r, MatchModes modeFrom modeTo) => TransferFunc modeFrom emit am (GenericCall modeTo -> r) Source # 
Instance details

Defined in Test.Cleveland.Internal.Actions.Transfer

Methods

transfer'r :: GenericTransferData modeFrom -> GenericCall modeTo -> r Source #

data TransferMode Source #

Data-kind for tracking what type of call we're making.

transfer :: forall addr r. (HasCallStack, TransferFunc ('Incomplete (InitialTransferMode addr)) 'TransferIgnoreResult 'HasNoAmount r, ToL1Address addr) => addr -> r Source #

Base method for making a transfer.

You can specify additional arguments after the destination address to modify optional transfer arguments. Those can either be Mutez to specify transfer amount (0 by default), or a specially constructed call descriptor. The order is arbitrary, but it is usually more convenient to specify transfer amount first. For example:

transfer addr [tz|123u|] $ calling (ep @"Entrypoint") ()
transfer addr [tz|123u|]

If the call isn't specified, then the default entrypoint will be called with (), i.e.

transfer addr

is functionally the same as

transfer addr $ calling def ()

If the address in the first argument is untyped, the transfer is unchecked. Unchecked transfers must use unsafeCalling for the call specification. You can also use unsafeCalling with typed address to force an unchecked transfer.

See Test.Cleveland.Internal.Actions.Transfer for further explanation of the interface.

By default, the sender is the account associated with the moneybag alias. This can be overridden with the --cleveland-moneybag-alias command line option, the TASTY_CLEVELAND_MONEYBAG_ALIAS env var, or withSender.

In some polymorphic cases, you may need to add HasEntrypointArg constraint:

>>> :{
example
  :: (MonadCleveland caps m, NiceParameter cp)
  => ContractHandle cp st vd -> m ()
example ch = transfer ch (123 :: Mutez)
:}
...
... Can not look up entrypoints in type
...   cp
... The most likely reason it is ambiguous, or you need
...   HasEntrypointArg cp (EntrypointRef 'Nothing) ()
... constraint
...

You can fix this by adding the constraint:

>>> :{
example
  :: ( MonadCleveland caps m, NiceParameter cp
     , HasEntrypointArg cp (EntrypointRef 'Nothing) ())
  => ContractHandle cp st vd -> m ()
example ch = transfer ch (123 :: Mutez)
:}

GHC may not always figure out the type of the entrypoint parameter. In that case, it'll show unbound type variable, usually arg0:

>>> :{
example
  :: (MonadCleveland caps m, NiceParameter cp, NiceParameter arg)
  => ContractHandle cp st vd -> arg -> m ()
example ch x = transfer ch (123 :: Mutez) $ calling def x
:}
...
... Can not look up entrypoints in type
...   cp
... The most likely reason it is ambiguous, or you need
...   HasEntrypointArg cp (EntrypointRef 'Nothing) arg0
... constraint
...

Either specifying a concrete type in the constraint, or leaving it polymorphic, fixes this:

>>> :{
example
  :: ( MonadCleveland caps m, NiceParameter cp, NiceParameter arg
     , HasEntrypointArg cp (EntrypointRef 'Nothing) Integer)
  => ContractHandle cp st vd -> Integer -> m ()
example ch x = transfer ch (123 :: Mutez) $ calling def x
:}
>>> :{
example
  :: ( MonadCleveland caps m, NiceParameter cp, NiceParameter arg
     , HasEntrypointArg cp (EntrypointRef 'Nothing) arg)
  => ContractHandle cp st vd -> arg -> m ()
example ch x = transfer ch (123 :: Mutez) $ calling def x
:}

initialData :: ToL1Address addr => addr -> GenericTransferData ('Incomplete (InitialTransferMode addr)) Source #

Construct initial GenericTransferData for a given address.

calling :: forall mname. EntrypointRef mname -> forall epArg param. (NiceParameter epArg, HasEntrypointArg param (EntrypointRef mname) epArg) => epArg -> GenericCall ('Checked param) Source #

Safely call an entrypoint specified by the first argument with the provided parameter.

The first character of the entrypoint name must be capitalized.

This is "safe" in the sense that the contract is checked if it indeed has the specified entrypoint and the entrypoint in question accepts the argument provided, a type error is raised otherwise.

transfer addr $ calling (ep @"Entrypoint") ()

Use CallDefault or def to call the default entrypoint.

transfer addr $ calling def ()

Notice that type variables for entrypoint argument and full parameter are specified after the entrypoint. This is done so more for readability. F. ex.:

transfer addr $ calling def @Integer 123

This does also marginally simplify type inference in the case of partial application.

unsafeCalling :: EpName -> forall epArg. NiceParameter epArg => epArg -> GenericCall 'Unchecked Source #

Unsafely call an entrypoint specified by the first argument with the provided parameter.

This is "unsafe" in the sense that there is no check that the contract indeed has the specified entrypoint or that the entrypoint in question accepts the argument provided.

Also, no compile-time checks are performed on the entrypoint name, so it can be malformed.

transfer addr $ unsafeCalling (ep @"Entrypoint") ()

Overloaded labels are supported with unsafeCalling, so you can specify the entrypoint as an overloaded label:

transfer addr $ unsafeCalling #entrypoint ()

Use DefEpName or def to call the default entrypoint.

Notice that the type variable for the entrypoint argument is specified after the entrypoint. This is done so more for readability. F. ex.:

transfer addr $ calling def @Integer 123

This does also marginally simplify type inference in the case of partial application.