morley-1.4.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.EntryPoints

Contents

Description

Utilities for lightweight entrypoints support.

Synopsis

Documentation

data EpAddress Source #

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

Constructors

EpAddress 

Fields

Instances

Instances details
Eq EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Ord EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep EpAddress :: Type -> Type #

Arbitrary FieldAnn => Arbitrary EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

NFData EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpAddress -> Builder #

IsoValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T Source #

TypeHasDoc EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep EpAddress Source # 
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 ToT EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

data ParseEpAddressError Source #

Instances

Instances details
Eq ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep ParseEpAddressError :: Type -> Type #

NFData ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: ParseEpAddressError -> () #

Buildable ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep ParseEpAddressError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep ParseEpAddressError = D1 ('MetaData "ParseEpAddressError" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "ParseEpAddressBadAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParseAddressError)) :+: (C1 ('MetaCons "ParseEpAddressBadRefAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "ParseEpAddressRefAnnError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpNameFromRefAnnError))))

parseEpAddress :: Text -> Either ParseEpAddressError EpAddress Source #

Parse an address which can be suffixed with entrypoint name (e.g. "tz1faswCTDciRzE4oJ9jn2Vm2dvjeyA9fUzU%entrypoint").

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.

Constructors

ParamNotesUnsafe 

Fields

Instances

Instances details
Eq (ParamNotes t) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

(==) :: ParamNotes t -> ParamNotes t -> Bool #

(/=) :: ParamNotes t -> ParamNotes t -> Bool #

Show (ParamNotes t) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic (ParamNotes t) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep (ParamNotes t) :: Type -> Type #

Methods

from :: ParamNotes t -> Rep (ParamNotes t) x #

to :: Rep (ParamNotes t) x -> ParamNotes t #

NFData (ParamNotes t) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: ParamNotes t -> () #

type Rep (ParamNotes t) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep (ParamNotes t) = D1 ('MetaData "ParamNotes" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "ParamNotesUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "pnNotes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Notes t)) :*: S1 ('MetaSel ('Just "pnRootAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RootAnn)))

pattern ParamNotes :: Notes t -> RootAnn -> ParamNotes t Source #

starParamNotes :: SingI t => ParamNotes t Source #

Parameter without annotations.

data ArmCoord Source #

Constructors

AcLeft 
AcRight 

Instances

Instances details
Eq ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep ArmCoord :: Type -> Type #

Methods

from :: ArmCoord -> Rep ArmCoord x #

to :: Rep ArmCoord x -> ArmCoord #

NFData ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: ArmCoord -> () #

Buildable ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: ArmCoord -> Builder #

type Rep ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep ArmCoord = D1 ('MetaData "ArmCoord" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "AcLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AcRight" 'PrefixI 'False) (U1 :: Type -> Type))

type ArmCoords = [ArmCoord] Source #

Coordinates of "arm" in Or tree, used solely in error messages.

data ParamEpError Source #

Errors specific to parameter type declaration (entrypoints).

Instances

Instances details
Eq ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep ParamEpError :: Type -> Type #

NFData ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: ParamEpError -> () #

Buildable ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep ParamEpError Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep ParamEpError = D1 ('MetaData "ParamEpError" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "ParamEpDuplicatedNames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty EpName))) :+: C1 ('MetaCons "ParamEpUncallableArm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ArmCoords)))

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.

Constructors

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

Instances details
Eq (EpLiftSequence arg param) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

(==) :: EpLiftSequence arg param -> EpLiftSequence arg param -> Bool #

(/=) :: EpLiftSequence arg param -> EpLiftSequence arg param -> Bool #

Show (EpLiftSequence arg param) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

showsPrec :: Int -> EpLiftSequence arg param -> ShowS #

show :: EpLiftSequence arg param -> String #

showList :: [EpLiftSequence arg param] -> ShowS #

NFData (EpLiftSequence param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: EpLiftSequence param arg -> () #

Buildable (EpLiftSequence arg param) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpLiftSequence arg param -> Builder #

data EntryPointCallT (param :: T) (arg :: T) Source #

Reference for calling a specific entrypoint of type arg.

Constructors

ParameterScope arg => EntryPointCall 

Fields

Instances

Instances details
Eq (EntryPointCallT param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

(==) :: EntryPointCallT param arg -> EntryPointCallT param arg -> Bool #

(/=) :: EntryPointCallT param arg -> EntryPointCallT param arg -> Bool #

Show (EntryPointCallT param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

showsPrec :: Int -> EntryPointCallT param arg -> ShowS #

show :: EntryPointCallT param arg -> String #

showList :: [EntryPointCallT param arg] -> ShowS #

NFData (EntryPointCallT param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: EntryPointCallT param arg -> () #

Buildable (EntryPointCallT param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

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.

Constructors

forall param.ParameterScope param => SomeEpc (EntryPointCallT param arg) 

Instances

Instances details
Eq (SomeEntryPointCallT arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show (SomeEntryPointCallT arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

NFData (SomeEntryPointCallT arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: SomeEntryPointCallT arg -> () #

Buildable (SomeEntryPointCallT arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

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.

type family ForbidOr (t :: T) :: Constraint where ... Source #

Equations

ForbidOr ('TOr l r) = TypeError ('Text "Cannot apply to sum type parameter " :<>: 'ShowType ('TOr l r)) 
ForbidOr _ = () 

data MkEntryPointCallRes param where Source #

Constructors

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.

flattenEntryPoints :: SingI t => ParamNotes t -> Map EpName Type Source #

Flatten a provided list of notes to a map of its entrypoints and its corresponding utype. Please refer to mkEntrypointsMap in regards to how duplicate entrypoints are handled.

Re-exports

newtype EpName Source #

Entrypoint name.

Empty if this entrypoint is default one. Cannot be equal to "default", the reference implementation forbids that. Also, set of allowed characters should be the same as in annotations.

Constructors

EpNameUnsafe 

Fields

Instances

Instances details
Eq EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

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

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

Ord EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Show EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Generic EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Associated Types

type Rep EpName :: Type -> Type #

Methods

from :: EpName -> Rep EpName x #

to :: Rep EpName x -> EpName #

Arbitrary FieldAnn => Arbitrary EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

NFData EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

rnf :: EpName -> () #

ToJSON EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

FromJSON EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Default EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

def :: EpName #

Buildable EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

build :: EpName -> Builder #

HasCLReader EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

type Rep EpName Source # 
Instance details

Defined in Michelson.Untyped.EntryPoints

type Rep EpName = D1 ('MetaData "EpName" "Michelson.Untyped.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'True) (C1 ('MetaCons "EpNameUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

epNameFromParamAnn :: FieldAnn -> Maybe EpName Source #

Make up EpName from annotation in parameter type declaration.

Returns Nothing if no entrypoint is assigned here.

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 (e.g. annotation in CONTRACT instruction).

Fails if annotation is invalid.

epNameToRefAnn :: EpName -> FieldAnn Source #

Turn entrypoint name into annotation used as reference to entrypoint.

data EpNameFromRefAnnError Source #