lorentz-0.14.1: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
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:

TypeType safe?What it refers toMichelson reflection
AddressNoWhole contractaddress
EpAddressNoEntrypointaddress
TAddressYesWhole contractaddress
FutureContractYesEntrypointaddress
ContractRefYesEntrypointcontract

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 :: Type) (vd :: Type) Source #

Address which remembers the parameter and views types 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
(cp ~ cp', vd ~ vd') => ToTAddress cp vd (TAddress cp' vd') Source # 
Instance details

Defined in Lorentz.Address

Methods

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

(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 vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toContractRef :: TAddress cp vd -> ContractRef arg Source #

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

Defined in Lorentz.Coercions

Methods

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

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

Defined in Lorentz.Coercions

Methods

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

Generic (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

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

Methods

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

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

Show (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

showsPrec :: Int -> TAddress p vd -> ShowS #

show :: TAddress p vd -> String #

showList :: [TAddress p vd] -> ShowS #

Buildable (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

build :: TAddress p vd -> Builder #

Eq (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

(==) :: TAddress p vd -> TAddress p vd -> Bool #

(/=) :: TAddress p vd -> TAddress p vd -> Bool #

Ord (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

compare :: TAddress p vd -> TAddress p vd -> Ordering #

(<) :: TAddress p vd -> TAddress p vd -> Bool #

(<=) :: TAddress p vd -> TAddress p vd -> Bool #

(>) :: TAddress p vd -> TAddress p vd -> Bool #

(>=) :: TAddress p vd -> TAddress p vd -> Bool #

max :: TAddress p vd -> TAddress p vd -> TAddress p vd #

min :: TAddress p vd -> TAddress p vd -> TAddress p vd #

ToAddress (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: TAddress cp vd -> Address Source #

HasAnnotation (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

HasRPCRepr (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type AsRPC (TAddress cp vd)

(TypeHasDoc p, ViewsDescriptorHasDoc vd) => TypeHasDoc (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (TAddress p vd) :: FieldDescriptions #

Methods

typeDocName :: Proxy (TAddress p vd) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (TAddress p vd) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (TAddress p vd) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (TAddress p vd) #

typeDocMichelsonRep :: TypeDocMichelsonRep (TAddress p vd) #

IsoValue (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p vd) :: T #

Methods

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

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

type Rep (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p vd) = D1 ('MetaData "TAddress" "Lorentz.Address" "lorentz-0.14.1-inplace" 'True) (C1 ('MetaCons "TAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address)))
type AsRPC (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

type AsRPC (TAddress cp vd) = TAddress cp vd
type TypeDocFieldDescriptions (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

type ToT (TAddress p vd) = GValueType (Rep (TAddress p vd))

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

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

HasRPCRepr (FutureContract p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type AsRPC (FutureContract p)

TypeHasDoc p => TypeHasDoc (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

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

Defined in Lorentz.Coercions

type AsRPC (FutureContract p) Source # 
Instance details

Defined in Lorentz.Address

type AsRPC (FutureContract p) = FutureContract p
type TypeDocFieldDescriptions (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Conversions

asAddressOf :: contract cp st vd -> Address -> TAddress cp vd Source #

For a contract and an address of its instance, construct a typed address.

asAddressOf_ :: contract cp st vd -> (Address ': s) :-> (TAddress cp vd ': s) Source #

callingAddress :: forall cp vd addr mname. (ToTAddress cp vd addr, NiceParameterFull cp) => addr -> EntrypointRef mname -> ContractRef (GetEntrypointArgCustom cp mname) Source #

Turn any typed address 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).

callingDefAddress :: forall cp vd addr. (ToTAddress cp vd addr, NiceParameterFull cp) => addr -> ContractRef (GetDefaultEntrypointArg cp) Source #

Specialization of callingAddress 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 L1Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: L1Address -> Address Source #

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (KindedAddress kind) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: KindedAddress kind -> Address Source #

ToAddress (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: TAddress cp vd -> Address Source #

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

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

Methods

toTAddress :: a -> TAddress cp vd Source #

Instances

Instances details
ToTAddress cp vd Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: Address -> TAddress cp vd Source #

ToTAddress cp vd ContractAddress Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: ContractAddress -> TAddress cp vd Source #

(cp ~ (), vd ~ ()) => ToTAddress cp vd ImplicitAddress Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: ImplicitAddress -> TAddress cp vd Source #

ToTAddress cp vd L1Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: L1Address -> TAddress cp vd Source #

(cp ~ Txr1CallParam a, vd ~ ()) => ToTAddress cp vd TxRollupAddress Source # 
Instance details

Defined in Lorentz.Txr1Call

Methods

toTAddress :: TxRollupAddress -> TAddress cp vd Source #

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

Defined in Lorentz.Address

Methods

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

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

Something coercible to 'TAddress cp'.

toTAddress_ :: forall cp addr vd s. ToTAddress_ cp vd addr => (addr ': s) :-> (TAddress cp vd ': 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 vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toContractRef :: TAddress cp vd -> ContractRef arg Source #

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

Convert something from ContractRef in Haskell world.

Methods

fromContractRef :: ContractRef cp -> contract Source #

Instances

Instances details
FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp Address 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

type Address = ConstrainedAddress '['AddressKindImplicit, 'AddressKindContract, 'AddressKindTxRollup] #

data EpAddress #

Constructors

EpAddress' 

Bundled Patterns

pattern EpAddress :: forall (kind :: AddressKind). () => KindedAddress kind -> EpName -> EpAddress 

Instances

Instances details
Generic EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Associated Types

type Rep EpAddress :: Type -> Type #

Show EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

NFData EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

build :: EpAddress -> Builder #

Eq EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Ord EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation EpAddress Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr EpAddress 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC EpAddress

TypeHasDoc EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions EpAddress :: FieldDescriptions #

IsoValue EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

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 Morley.Michelson.Typed.Entrypoints

type Rep EpAddress = D1 ('MetaData "EpAddress" "Morley.Michelson.Typed.Entrypoints" "morley-1.18.0-inplace" '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 AsRPC EpAddress 
Instance details

Defined in Morley.AsRPC

type AsRPC EpAddress = EpAddress
type TypeDocFieldDescriptions EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT EpAddress = 'TAddress

data ContractRef arg #

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

Show (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

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

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

IsoValue (ContractRef arg) => Buildable (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

Eq (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

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

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

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

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

Defined in Lorentz.Annotation

HasRPCRepr (ContractRef arg) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (ContractRef arg)

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

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (ContractRef cp) :: FieldDescriptions #

(HasNoOpToT arg, WellTypedToT arg) => IsoValue (ContractRef arg) 
Instance details

Defined in Morley.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 #

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 AsRPC (ContractRef arg) 
Instance details

Defined in Morley.AsRPC

type AsRPC (ContractRef arg) = ContractRef arg
type TypeDocFieldDescriptions (ContractRef cp) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

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