lorentz-0.4.0: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Address

Description

This module introduces several types for safe work with address and contract types. All available types for that are represented in the following table:

Type Type safe? What it refers to Michelson reflection
Address No Whole contract address
EpAddress No Entrypoint address
TAddress Yes Whole contract address
FutureContract Yes Entrypoint address
ContractRef Yes Entrypoint contract

This module also provides functions for converting between these types in Haskell and Michelson worlds. In the latter you can additionally use coercions and dedicated instructions from Lorentz.Instr.

Synopsis

Documentation

newtype TAddress p Source #

Address which remembers the parameter type of the contract it refers to.

It differs from Michelson's contract type because it cannot contain entrypoint, and it always refers to entire contract parameter even if this contract has explicit default entrypoint.

Constructors

TAddress 

Fields

Instances

Instances details
(FailWhen cond msg, cond ~ (CanHaveEntryPoints cp && Not (ParameterEntryPointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntryPointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

Generic (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type Rep (TAddress p) :: Type -> Type #

Methods

from :: TAddress p -> Rep (TAddress p) x #

to :: Rep (TAddress p) x -> TAddress p #

IsoValue (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p) :: T #

Methods

toVal :: TAddress p -> Value (ToT (TAddress p)) #

fromVal :: Value (ToT (TAddress p)) -> TAddress p #

HasTypeAnn (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) = D1 ('MetaData "TAddress" "Lorentz.Address" "lorentz-0.4.0-4bB2PLHB7038abCZLw1vnA" 'True) (C1 ('MetaCons "TAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address)))
type ToT (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

newtype FutureContract arg Source #

Address associated with value of contract arg type.

Places where ContractRef can appear are now severely limited, this type gives you type-safety of ContractRef but still can be used everywhere. This type is not a full-featured one rather a helper; in particular, once pushing it on stack, you cannot return it back to Haskell world.

Note that it refers to an entrypoint of the contract, not just the contract as a whole. In this sense this type differs from TAddress.

Unlike with ContractRef, having this type you still cannot be sure that the referred contract exists and need to perform a lookup before calling it.

Constructors

FutureContract 

Instances

Instances details
cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

HasTypeAnn (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type ToT (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Conversions

callingTAddress :: forall cp mname. NiceParameterFull cp => TAddress cp -> EntryPointRef mname -> ContractRef (GetEntryPointArgCustom cp mname) Source #

Turn TAddress to ContractRef in Haskell world.

This is an analogy of address to contract convertion in Michelson world, thus you have to supply an entrypoint (or call the default one explicitly).

callingDefTAddress :: forall cp. NiceParameterFull cp => TAddress cp -> ContractRef (GetDefaultEntryPointArg cp) Source #

Specification of callTAddress to call the default entrypoint.

class ToAddress a where Source #

Convert something to Address in Haskell world.

Use this when you want to access state of the contract and are not interested in calling it.

Methods

toAddress :: a -> Address Source #

Instances

Instances details
ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class ToTAddress (cp :: Type) (a :: Type) where Source #

Convert something referring to a contract (not specific entrypoint) to TAddress in Haskell world.

Methods

toTAddress :: a -> TAddress cp Source #

Instances

Instances details
ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

type ToTAddress_ cp addr = (ToTAddress cp addr, ToT addr ~ ToT Address) Source #

Something coercible to 'TAddress cp'.

toTAddress_ :: forall cp addr s. ToTAddress_ cp addr => (addr ': s) :-> (TAddress cp ': s) Source #

Cast something appropriate to TAddress.

class ToContractRef (cp :: Type) (contract :: Type) where Source #

Convert something to ContractRef in Haskell world.

Methods

toContractRef :: HasCallStack => contract -> ContractRef cp Source #

Instances

Instances details
(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

(FailWhen cond msg, cond ~ (CanHaveEntryPoints cp && Not (ParameterEntryPointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntryPointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class FromContractRef (cp :: Type) (contract :: Type) where Source #

Convert something from ContractAddr in Haskell world.

Methods

fromContractRef :: ContractRef cp -> contract Source #

Instances

Instances details
FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

convertContractRef :: forall cp contract2 contract1. (ToContractRef cp contract1, FromContractRef cp contract2) => contract1 -> contract2 Source #

Re-exports

data Address #

Data type corresponding to address structure in Tezos.

Instances

Instances details
Eq Address 
Instance details

Defined in Tezos.Address

Methods

(==) :: Address -> Address -> Bool #

(/=) :: Address -> Address -> Bool #

Ord Address 
Instance details

Defined in Tezos.Address

Show Address 
Instance details

Defined in Tezos.Address

Generic Address 
Instance details

Defined in Tezos.Address

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

Arbitrary Address 
Instance details

Defined in Tezos.Address

NFData Address 
Instance details

Defined in Tezos.Address

Methods

rnf :: Address -> () #

ToJSON Address 
Instance details

Defined in Tezos.Address

ToJSONKey Address 
Instance details

Defined in Tezos.Address

FromJSON Address 
Instance details

Defined in Tezos.Address

FromJSONKey Address 
Instance details

Defined in Tezos.Address

Buildable Address 
Instance details

Defined in Tezos.Address

Methods

build :: Address -> Builder #

TypeHasDoc Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

HasCLReader Address 
Instance details

Defined in Tezos.Address

HasTypeAnn Address Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

type Rep Address 
Instance details

Defined in Tezos.Address

type Rep Address = D1 ('MetaData "Address" "Tezos.Address" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "KeyAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHash)) :+: C1 ('MetaCons "ContractAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ContractHash)))
type TypeDocFieldDescriptions Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

data EpAddress #

Address with optional entrypoint name attached to it. TODO: come up with better name?

Constructors

EpAddress 

Fields

Instances

Instances details
Eq EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Ord EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Show EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep EpAddress :: Type -> Type #

Arbitrary FieldAnn => Arbitrary EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

NFData EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpAddress -> Builder #

TypeHasDoc EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

HasTypeAnn EpAddress Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type Rep EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep EpAddress = D1 ('MetaData "EpAddress" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "EpAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "eaAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Address) :*: S1 ('MetaSel ('Just "eaEntryPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpName)))
type TypeDocFieldDescriptions EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

data ContractRef arg #

Since Contract name is used to designate contract code, lets call analogy of TContract type as follows.

Note that type argument always designates an argument of entrypoint. If a contract has explicit default entrypoint (and no root entrypoint), ContractRef referring to it can never have the entire parameter as its type argument.

Instances

Instances details
cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

Eq (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(==) :: ContractRef arg -> ContractRef arg -> Bool #

(/=) :: ContractRef arg -> ContractRef arg -> Bool #

Show (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

WellTypedToT arg => Buildable (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

PolyTypeHasDocC '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

WellTypedToT arg => IsoValue (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T #

Methods

toVal :: ContractRef arg -> Value (ToT (ContractRef arg)) #

fromVal :: Value (ToT (ContractRef arg)) -> ContractRef arg #

HasTypeAnn a => HasTypeAnn (ContractRef a) Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo a1 a2 => CanCastTo (ContractRef a1 :: Type) (ContractRef a2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ContractRef a1) -> Proxy (ContractRef a2) -> () Source #

type TypeDocFieldDescriptions (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (ContractRef arg) = 'TContract (ToT arg)

coerceContractRef :: ToT a ~ ToT b => ContractRef a -> ContractRef b #

Replace type argument of ContractAddr with isomorphic one.