morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Typed.Operation

Synopsis

Documentation

newtype OperationHash Source #

Constructors

OperationHash 

Instances

Instances details
Generic OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Associated Types

type Rep OperationHash :: Type -> Type #

Show OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

NFData OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

rnf :: OperationHash -> () #

Eq OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Ord OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

type Rep OperationHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

type Rep OperationHash = D1 ('MetaData "OperationHash" "Morley.Michelson.Typed.Operation" "morley-1.20.0-inplace" 'True) (C1 ('MetaCons "OperationHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unOperationHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data OriginationOperation Source #

Data necessary to originate a contract.

Constructors

forall cp st kind.(StorageScope st, ParameterScope cp, L1AddressKind kind) => OriginationOperation 

Fields

Instances

Instances details
Show OriginationOperation Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Buildable OriginationOperation Source #

Prettyprinter for OriginationOperation

>>> :{
contract
  :: (StorageScope storage, ConstantScope storage)
  => Contract TUnit storage
contract = defaultContract FAILWITH
:}
>>> let ia = [ta|tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH|]
>>> pretty $ OriginationOperation ia Nothing [tz|123u|] VUnit contract 1 Nothing
Originate a contract with delegate <nobody> initial storage 'Unit' and balance
123 μꜩ
>>> :{
pretty $ OriginationOperation ia (Just $ unImplicitAddress ia)
  [tz|123u|] VUnit contract 1 Nothing
:}
Originate a contract with delegate tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH initial
storage 'Unit' and balance 123 μꜩ
>>> :{
pretty $ OriginationOperation ia Nothing
  [tz|123u|] VUnit contract 1 (Just $ mkAlias "some_alias")
:}
Originate contract some_alias with delegate <nobody> initial storage 'Unit' and
balance 123 μꜩ
>>> let storage = toVal (((), ()), ((), ()))
>>> :{
pretty $ OriginationOperation ia Nothing [tz|123u|] storage contract 1 Nothing
:}
Originate a contract with delegate <nobody> initial storage
  Pair (Pair Unit Unit) (Pair Unit Unit)
and balance 123 μꜩ
Instance details

Defined in Morley.Michelson.Typed.Operation

data TransferOperation Source #

Data necessary to send a transaction to given address which is assumed to be the address of an originated contract.

Instances

Instances details
Show TransferOperation Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Buildable TransferOperation Source #

Prettyprinter for TransferOperation

>>> let ia = [ta|tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH|]
>>> let ca = [ta|KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz|]
>>> :{
transfer
  :: (IsoValue p, ParameterScope (ToT p))
  => KindedAddress kind -> p -> TransferOperation
transfer dest param =
  TransferOperation (Constrained dest) (TxData (Constrained ia)
    (TxTypedParam $ toVal param) DefEpName [tz|123u|]) 1
:}
>>> pretty $ transfer ia ()
Transfer 123 μꜩ tokens from tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH to
tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH
>>> pretty $ transfer ca ()
Transfer to KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz entrypoint <default> from
tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH with parameter 'Unit' and amount 123 μꜩ
>>> pretty $ transfer ca (MkAddress ca, MkAddress ia)
Transfer to KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz entrypoint <default> from
tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH with parameter
  Pair
    "KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz"
    "tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH"
and amount 123 μꜩ
Instance details

Defined in Morley.Michelson.Typed.Operation

data SetDelegateOperation Source #

Set contract's delegate

Constructors

SetDelegateOperation 

Fields

Instances

Instances details
Show SetDelegateOperation Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Buildable SetDelegateOperation Source #

Prettyprinter for SetDelegateOperation

>>> let ia = [ta|tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH|]
>>> pretty $ SetDelegateOperation (Constrained ia) Nothing 1
Set delegate of contract tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH to <nobody>
>>> :{
pretty $ SetDelegateOperation (Constrained ia) (Just $ unImplicitAddress ia) 1
:}
Set delegate of contract tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH to
tz29EDhZ4D3XueHxm5RGZsJLHRtj3qSA2MzH
Instance details

Defined in Morley.Michelson.Typed.Operation

data EmitOperation Source #

Constructors

forall t.PackedValScope t => EmitOperation 

Instances

Instances details
Show EmitOperation Source # 
Instance details

Defined in Morley.Michelson.Typed.Operation

Buildable EmitOperation Source #

Prettyprinter for EmitOperation

>>> let ca = [ta|KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz|]
>>> :{
emit :: (IsoValue a, PackedValScope (ToT a)) => a -> EmitOperation
emit val = EmitOperation ca $ Emit "tag" starNotes (toVal val) 1
:}
>>> pretty $ emit ()
Emit event 'tag' with type 'unit' and value 'Unit' from contract
KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz
>>> let tup = (((), ()), ((), ()))
>>> let largeTup = (tup, tup)
>>> pretty $ emit largeTup
Emit event 'tag' with type
  pair (pair (pair unit unit) unit unit) (pair unit unit) unit unit
and value
  Pair
    (Pair (Pair Unit Unit) (Pair Unit Unit))
    (Pair (Pair Unit Unit) (Pair Unit Unit))
from contract KT19upy4rX95WF5R3aCNgrtYA8926GP6fuJz
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

build :: EmitOperation -> Doc

buildList :: [EmitOperation] -> Doc

mkContractAddress :: OperationHash -> GlobalCounter -> ContractAddress Source #

Compute address of a contract from its origination operation and global counter.

However, in real Tezos encoding of the operation is more than just OriginationOperation. There an Operation has several more meta-fields plus a big sum-type of all possible operations.

See here: https://gitlab.com/tezos/tezos/-/blob/f57c50e3a657956d69a1699978de9873c98f0018/src/proto_006_PsCARTHA/lib_protocol/operation_repr.ml#L78

In other words, contract hash is calculated as the blake2b160 (20-byte) hash of origination operation hash + word64 global counter.

In Morley we do not yet support full encoding of Tezos Operations, therefore we choose to generate contract addresses in a simplified manner.

Namely, we encode OriginationOperation as we can and concat it with the global counter.

Then we take blake2b160 hash of the resulting bytes and consider it to be the contract's address.