morley-0.5.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.EntryPoints

Description

Utilities for lightweight entrypoints support.

Synopsis

Documentation

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
Eq EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

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

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

Ord EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Arbitrary FieldAnn => Arbitrary EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Default EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

def :: EpName #

Buildable EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpName -> Builder #

pattern NoEpName :: EpName Source #

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 EpAddress Source #

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

Constructors

EpAddress 

Fields

Instances
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

Arbitrary FieldAnn => Arbitrary EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

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 #

IsoCValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT EpAddress :: CT Source #

TypeHasDoc EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Value

CompareOpHs EpAddress Source # 
Instance details

Defined in Lorentz.Arith

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

NiceParameter cp => ToContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

type ToT EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

parseEpAddress :: Text -> Either ParseEpAddressError EpAddress Source #

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

newtype 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
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

data ArmCoord Source #

Constructors

AcLeft 
AcRight 
Instances
Eq ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Buildable ArmCoord Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: ArmCoord -> Builder #

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).

mkParamNotes :: Notes t -> 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 :: EpLiftSequence arg subparam -> EpLiftSequence arg (TOr subparam r) 
EplWrapRight :: EpLiftSequence arg subparam -> EpLiftSequence arg (TOr l subparam) 
Instances
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 #

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

EntryPointCall 

Fields

Instances
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 #

param ~ arg => Default (EntryPointCallT param arg) Source #

Calls the default entrypoint.

Instance details

Defined in Michelson.Typed.EntryPoints

Methods

def :: EntryPointCallT param arg #

Buildable (EntryPointCallT param arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EntryPointCallT param arg -> Builder #

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

ParameterScope param => SomeEpc (EntryPointCallT param arg) 

mkEntryPointCall :: ParameterScope param => EpName -> (Sing param, Notes param) -> (forall arg. ParameterScope arg => (Notes arg, EntryPointCallT param arg) -> r) -> Maybe r 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 :: (Sing TUnit, Notes TUnit) Source #

For implicit account, which type its parameter seems to have from outside.