morley-0.7.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.EntryPoints.Doc

Description

Utilities for declaring and documenting entry points.

Synopsis

Documentation

data DEntryPoint (kind :: Type) Source #

Gathers information about single entrypoint.

We assume that entry points might be of different kinds, which is designated by phantom type parameter. For instance, you may want to have several groups of entry points corresponding to various parts of a contract - specifying different kind type argument for each of those groups will allow you defining different DocItem instances with appropriate custom descriptions for them.

Constructors

DEntryPoint 

Fields

class EntryArrow kind name body where Source #

Provides arror for convenient entrypoint documentation

Methods

(#->) :: (Label name, Proxy kind) -> body -> body Source #

Lift entrypoint implementation.

Entrypoint names should go with "e" prefix.

Instances
(name ~ AppendSymbol "e" epName, body ~ ((param & s) :-> out), KnownSymbol epName, DocItem (DEntryPoint kind), TypeHasDoc param, HasTypeAnn param, KnownValue param) => EntryArrow (kind :: Type) name body Source # 
Instance details

Defined in Lorentz.EntryPoints.Doc

Methods

(#->) :: (Label name, Proxy kind) -> body -> body Source #

diEntryPointToMarkdown :: HeaderLevel -> DEntryPoint level -> Markdown Source #

Default implementation of docItemToMarkdown for entry points.

data DEntryPointArg Source #

Describes argument of an entrypoint.

Constructors

DEntryPointArg 

Fields

  • epaArg :: Maybe DType

    Argument of the entrypoint. Pass Nothing if no argument is required.

  • epaHasAnnotation :: Bool

    Whether this entrypoint has a field annotation (and thus is callable using the standard "lightweigth entrypoints" mechanism) or is a virtual entrypoint which requires constructing a value of the full parameter type.

  • epaBuilding :: [ParamBuildingStep]

    Describes a way to lift an entrypoint argument into full parameter which can be passed to the contract.

    Steps are supposed to be applied in the order in which they are given. E.g. suppose that an entrypoint is called as Run (Service1 arg); then the first step should describe wrapping into Service1 constructor, and the second step should be about wrapping into Run constructor.

  • epaType :: Type

    Untyped representation of entrypoint, used for printing its michelson type representation.

data DType where Source #

Doc element with description of a type.

Constructors

DType :: TypeHasDoc a => Proxy a -> DType 
Instances
Eq DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

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

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

Ord DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

compare :: DType -> DType -> Ordering #

(<) :: DType -> DType -> Bool #

(<=) :: DType -> DType -> Bool #

(>) :: DType -> DType -> Bool #

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

max :: DType -> DType -> DType #

min :: DType -> DType -> DType #

Show DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

DocItem DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemPosition DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemPlacement DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

class KnownSymbol con => DeriveCtorFieldDoc con (cf :: CtorField) where Source #

Pick a type documentation from CtorField.

data ParamBuildingStep Source #

Describes a parameter building step.

This can be wrapping into (Haskell) constructor, or a more complex transformation.

Constructors

ParamBuildingStep 

Fields

clarifyParamBuildingSteps :: ParamBuildingStep -> (inp :-> out) -> inp :-> out Source #

Go over contract code and update every occurrence of DEntryPointArg documentation item, adding the given step to its "how to build parameter" description.

mkUType :: Sing x -> Notes x -> Type Source #

mkDEpUType :: forall t. (KnownValue t, HasTypeAnn t) => Type Source #

type DocumentEntryPoints kind a = (Generic a, GDocumentEntryPoints kind (Rep a)) Source #

Constraint for documentEntryPoints.

documentEntryPoint :: forall kind epName param s out. (KnownSymbol epName, DocItem (DEntryPoint kind), TypeHasDoc param, HasTypeAnn param, KnownValue param) => ((param & s) :-> out) -> (param & s) :-> out Source #

Wrapper for documenting single entrypoint which parameter isn't going to be unwrapped from some datatype.

entryCase unwraps a datatype, however, sometimes we want to have entrypoint parameter to be not wrapped into some datatype.

entryCase :: forall dt entryPointKind out inp clauses. (CaseTC dt out inp clauses, DocumentEntryPoints entryPointKind dt) => Proxy entryPointKind -> IsoRecTuple clauses -> (dt & inp) :-> out Source #

Version of entryCase_ for tuples.

entryCase_ :: forall dt entryPointKind out inp. (InstrCaseC dt inp out, RMap (CaseClauses dt), DocumentEntryPoints entryPointKind dt) => Proxy entryPointKind -> Rec (CaseClauseL inp out) (CaseClauses dt) -> (dt & inp) :-> out Source #

Like case_, to be used for pattern-matching on parameter.

Modifies documentation accordingly. Including description of entrypoints' arguments, thus for them you will need to supply TypeHasDoc instance.