Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities for lightweight entrypoints support.
Synopsis
- data EpAddress = EpAddress {}
- data ParseEpAddressError
- formatEpAddress :: EpAddress -> Text
- mformatEpAddress :: EpAddress -> MText
- parseEpAddress :: Text -> Either ParseEpAddressError EpAddress
- unsafeParseEpAddress :: HasCallStack => Text -> EpAddress
- parseEpAddressRaw :: ByteString -> Either ParseEpAddressError EpAddress
- unsafeParseEpAddressRaw :: ByteString -> EpAddress
- data ParamNotes (t :: T) = ParamNotesUnsafe {}
- pattern ParamNotes :: Notes t -> RootAnn -> ParamNotes t
- starParamNotes :: SingI t => ParamNotes t
- data ArmCoord
- type ArmCoords = [ArmCoord]
- data ParamEpError
- mkParamNotes :: Notes t -> RootAnn -> Either ParamEpError (ParamNotes t)
- data EpLiftSequence (arg :: T) (param :: T) where
- EplArgHere :: EpLiftSequence arg arg
- EplWrapLeft :: (KnownT subparam, KnownT r) => EpLiftSequence arg subparam -> EpLiftSequence arg ('TOr subparam r)
- EplWrapRight :: (KnownT l, KnownT subparam) => EpLiftSequence arg subparam -> EpLiftSequence arg ('TOr l subparam)
- data EntrypointCallT (param :: T) (arg :: T) = ParameterScope arg => EntrypointCall {
- epcName :: EpName
- epcParamProxy :: Proxy param
- epcLiftSequence :: EpLiftSequence arg param
- epcPrimitive :: forall p. (ParameterScope p, ForbidOr p) => EntrypointCallT p p
- epcCallRootUnsafe :: ParameterScope param => EntrypointCallT param param
- data SomeEntrypointCallT (arg :: T) = forall param.ParameterScope param => SomeEpc (EntrypointCallT param arg)
- sepcCallRootUnsafe :: ParameterScope param => SomeEntrypointCallT param
- sepcPrimitive :: forall t. (ParameterScope t, ForbidOr t) => SomeEntrypointCallT t
- sepcName :: SomeEntrypointCallT arg -> EpName
- type family ForbidOr (t :: T) :: Constraint where ...
- data MkEntrypointCallRes param where
- MkEntrypointCallRes :: ParameterScope arg => Notes arg -> EntrypointCallT param arg -> MkEntrypointCallRes param
- mkEntrypointCall :: ParameterScope param => EpName -> ParamNotes param -> Maybe (MkEntrypointCallRes param)
- tyImplicitAccountParam :: ParamNotes 'TUnit
- newtype EpName = EpNameUnsafe {}
- pattern DefEpName :: EpName
- epNameFromParamAnn :: FieldAnn -> Maybe EpName
- epNameToParamAnn :: EpName -> FieldAnn
- epNameFromRefAnn :: FieldAnn -> Either EpNameFromRefAnnError EpName
- epNameToRefAnn :: EpName -> FieldAnn
- data EpNameFromRefAnnError = InEpNameBadAnnotation FieldAnn
Documentation
Address with optional entrypoint name attached to it. TODO: come up with better name?
EpAddress | |
|
Instances
data ParseEpAddressError Source #
Instances
formatEpAddress :: EpAddress -> Text Source #
mformatEpAddress :: EpAddress -> MText Source #
parseEpAddress :: Text -> Either ParseEpAddressError EpAddress Source #
Parse an address which can be suffixed with entrypoint name (e.g. "tz1faswCTDciRzE4oJ9jn2Vm2dvjeyA9fUzU%entrypoint").
unsafeParseEpAddress :: HasCallStack => Text -> EpAddress Source #
parseEpAddressRaw :: ByteString -> Either ParseEpAddressError EpAddress Source #
Parses byte representation of entrypoint address.
For every address
KT1QbdJ7M7uAQZwLpvzerUyk7LYkJWDL7eDh%foo%bar
we get the following byte representation
01afab866e7f1e74f9bba388d66b246276ce50bf4700666f6f25626172 ______________________________________//__/____ address % ep1 % ep2
data ParamNotes (t :: T) Source #
Annotations for contract parameter declaration.
Following the Michelson specification, this type has the following invariants:
1. No entrypoint name is duplicated.
2. If default
entrypoint is explicitly assigned, no "arm" remains uncallable.
Instances
pattern ParamNotes :: Notes t -> RootAnn -> ParamNotes t Source #
starParamNotes :: SingI t => ParamNotes t Source #
Parameter without annotations.
data ParamEpError Source #
Errors specific to parameter type declaration (entrypoints).
Instances
mkParamNotes :: Notes t -> RootAnn -> Either ParamEpError (ParamNotes t) Source #
Construct ParamNotes
performing all necessary checks.
data EpLiftSequence (arg :: T) (param :: T) where Source #
Describes how to construct full contract parameter from given entrypoint argument.
This could be just wrapper over Value arg -> Value param
, but we cannot
use Value
type in this module easily.
EplArgHere :: EpLiftSequence arg arg | |
EplWrapLeft :: (KnownT subparam, KnownT r) => EpLiftSequence arg subparam -> EpLiftSequence arg ('TOr subparam r) | |
EplWrapRight :: (KnownT l, KnownT subparam) => EpLiftSequence arg subparam -> EpLiftSequence arg ('TOr l subparam) |
Instances
Eq (EpLiftSequence arg param) Source # | |
Defined in Michelson.Typed.Entrypoints (==) :: EpLiftSequence arg param -> EpLiftSequence arg param -> Bool # (/=) :: EpLiftSequence arg param -> EpLiftSequence arg param -> Bool # | |
Show (EpLiftSequence arg param) Source # | |
Defined in Michelson.Typed.Entrypoints showsPrec :: Int -> EpLiftSequence arg param -> ShowS # show :: EpLiftSequence arg param -> String # showList :: [EpLiftSequence arg param] -> ShowS # | |
NFData (EpLiftSequence param arg) Source # | |
Defined in Michelson.Typed.Entrypoints rnf :: EpLiftSequence param arg -> () # | |
Buildable (EpLiftSequence arg param) Source # | |
Defined in Michelson.Typed.Entrypoints build :: EpLiftSequence arg param -> Builder # |
data EntrypointCallT (param :: T) (arg :: T) Source #
Reference for calling a specific entrypoint of type arg
.
ParameterScope arg => EntrypointCall | |
|
Instances
Eq (EntrypointCallT param arg) Source # | |
Defined in Michelson.Typed.Entrypoints (==) :: EntrypointCallT param arg -> EntrypointCallT param arg -> Bool # (/=) :: EntrypointCallT param arg -> EntrypointCallT param arg -> Bool # | |
Show (EntrypointCallT param arg) Source # | |
Defined in Michelson.Typed.Entrypoints showsPrec :: Int -> EntrypointCallT param arg -> ShowS # show :: EntrypointCallT param arg -> String # showList :: [EntrypointCallT param arg] -> ShowS # | |
NFData (EntrypointCallT param arg) Source # | |
Defined in Michelson.Typed.Entrypoints rnf :: EntrypointCallT param arg -> () # | |
Buildable (EntrypointCallT param arg) Source # | |
Defined in Michelson.Typed.Entrypoints build :: EntrypointCallT param arg -> Builder # |
epcPrimitive :: forall p. (ParameterScope p, ForbidOr p) => EntrypointCallT p p Source #
Call parameter which has no entrypoints, always safe.
epcCallRootUnsafe :: ParameterScope param => EntrypointCallT param param Source #
Construct EntrypointCallT
which calls no entrypoint and assumes that
there is no explicit "default" one.
Validity of such operation is not ensured.
data SomeEntrypointCallT (arg :: T) Source #
EntrypointCallT
with hidden parameter type.
This requires argument to satisfy ParameterScope
constraint.
Strictly speaking, entrypoint argument may one day start having different
set of constraints comparing to ones applied to parameter, but this seems
unlikely.
forall param.ParameterScope param => SomeEpc (EntrypointCallT param arg) |
Instances
Eq (SomeEntrypointCallT arg) Source # | |
Defined in Michelson.Typed.Entrypoints (==) :: SomeEntrypointCallT arg -> SomeEntrypointCallT arg -> Bool # (/=) :: SomeEntrypointCallT arg -> SomeEntrypointCallT arg -> Bool # | |
Show (SomeEntrypointCallT arg) Source # | |
Defined in Michelson.Typed.Entrypoints showsPrec :: Int -> SomeEntrypointCallT arg -> ShowS # show :: SomeEntrypointCallT arg -> String # showList :: [SomeEntrypointCallT arg] -> ShowS # | |
NFData (SomeEntrypointCallT arg) Source # | |
Defined in Michelson.Typed.Entrypoints rnf :: SomeEntrypointCallT arg -> () # | |
Buildable (SomeEntrypointCallT arg) Source # | |
Defined in Michelson.Typed.Entrypoints build :: SomeEntrypointCallT arg -> Builder # |
sepcCallRootUnsafe :: ParameterScope param => SomeEntrypointCallT param Source #
Construct SomeEntrypointCallT
which calls no entrypoint and assumes that
there is no explicit "default" one.
Validity of such operation is not ensured.
sepcPrimitive :: forall t. (ParameterScope t, ForbidOr t) => SomeEntrypointCallT t Source #
Call parameter which has no entrypoints, always safe.
sepcName :: SomeEntrypointCallT arg -> EpName Source #
type family ForbidOr (t :: T) :: Constraint where ... Source #
data MkEntrypointCallRes param where Source #
MkEntrypointCallRes :: ParameterScope arg => Notes arg -> EntrypointCallT param arg -> MkEntrypointCallRes param |
mkEntrypointCall :: ParameterScope param => EpName -> ParamNotes param -> Maybe (MkEntrypointCallRes param) Source #
Build EntrypointCallT
.
Here we accept entrypoint name and type information for the parameter of target contract.
Returns Nothing
if entrypoint is not found.
tyImplicitAccountParam :: ParamNotes 'TUnit Source #
Parameter type of implicit account.
Re-exports
Entrypoint name.
There are two properties we care about:
- Special treatment of the
default
entrypoint name.default
is prohibited in theCONTRACT
instruction and in values ofaddress
andcontract
types. However, it is not prohibited in theSELF
instruction. Hence, the value insideEpName
can be"default"
, so that we can distinguishSELF
andSELF %default
. It is important to distinguish them because their binary representation that is inserted into blockchain is different. For example, typecheckingSELF %default
consumes more gas thanSELF
. In this module, we provide several smart constructors with different handling ofdefault
, please use the appropriate one for your use case. - The set of permitted characters. Intuitively, an entrypoint name should
be valid only if it is a valid annotation (because entrypoints are defined
using field annotations). However, it is not enforced in Tezos.
It is not clear whether this behavior is intended. There is an upstream
issue which received
bug
label, so probably it is considered a bug. Currently we treat it as a bug and deviate from upstream implementation by probiting entrypoint names that are not valid annotations. If Tezos developers fix it soon, we will be happy. If they don't, we should (maybe temporarily) remove this limitation from our code. There is an issue in our repo as well.
Instances
Eq EpName Source # | |
Ord EpName Source # | |
Show EpName Source # | |
Generic EpName Source # | |
ToJSON EpName Source # | |
Defined in Michelson.Untyped.Entrypoints | |
FromJSON EpName Source # | |
NFData EpName Source # | |
Defined in Michelson.Untyped.Entrypoints | |
Buildable EpName Source # | |
Defined in Michelson.Untyped.Entrypoints | |
HasCLReader EpName Source # | |
Defined in Michelson.Untyped.Entrypoints | |
type Rep EpName Source # | |
Defined in Michelson.Untyped.Entrypoints |
pattern DefEpName :: EpName Source #
This is a bidirectional pattern that can be used for two purposes:
- Construct an
EpName
referring to the default entrypoint. - Use it in pattern-matching or in equality comparison to check whether
EpName
refers to the default entrypoint. This is trickier because there are two possibleEpName
values referring to the default entrypoints.DefEpName
will match only the most common one (no entrypoint). However, there is a special case:SELF
instruction can have explicit%default
reference. For this reason, it is recommended to useisDefEpName
instead. Pattern-matching onDefEpName
is still permitted for backwards compatibility and for the cases when you are sure thatEpName
does not come from theSELF
instruction.
epNameToParamAnn :: EpName -> FieldAnn Source #
Turn entrypoint name into annotation for contract parameter declaration.
epNameFromRefAnn :: FieldAnn -> Either EpNameFromRefAnnError EpName Source #
Make up EpName
from annotation which is reference to an entrypoint.
Note that it's more common for Michelson to prohibit explicit default
entrypoint reference.
Specifically, %default
annotation is probitited in values of address
and contract
types. It's also prohibited in the CONTRACT
instruction.
However, there is an exception: SELF %default
is a perfectly valid
instruction. Hence, when you construct an EpName
from an annotation
that's part of SELF
, you should use epNameFromSelfAnn
instead.
epNameToRefAnn :: EpName -> FieldAnn Source #
Turn entrypoint name into annotation used as reference to entrypoint.
data EpNameFromRefAnnError Source #