lorentz-0.11.0: EDSL 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

pattern DEntrypointDocItem :: DEntrypoint kind -> SomeDocItem Source #

Pattern that checks whether given SomeDocItem hides DEntrypoint inside (of any entrypoint kind).

In case a specific kind is necessary, use plain (cast -> Just DEntrypoint{..}) construction instead.

class Typeable ep => EntrypointKindHasDoc (ep :: Type) where Source #

Describes location of entrypoints of the given kind.

All such entrypoints will be placed under the same "entrypoints" section, and this instance defines characteristics of this section.

Minimal complete definition

entrypointKindPos, entrypointKindSectionName

Methods

entrypointKindPos :: Natural Source #

Position of the respective entrypoints section in the doc. This shares the same positions space with all other doc items.

entrypointKindSectionName :: Text Source #

Name of the respective entrypoints section.

entrypointKindSectionDescription :: Maybe Markdown Source #

Description in the respective entrypoints section.

entrypointSection :: EntrypointKindHasDoc kind => Text -> Proxy kind -> (i :-> o) -> i :-> o Source #

Mark code as part of entrypoint with given name.

This is automatically called at most of the appropriate situations, like entryCase calls.

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

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

Defined in Lorentz.Entrypoints.Doc

Methods

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

data CommonContractBehaviourKind Source #

Describes the behaviour common for all entrypoints.

For instance, if your contract runs some checks before calling any entrypoint, you probably want to wrap those checks into entrypointSection "Prior checks" (Proxy @CommonContractBehaviourKind).

data CommonEntrypointsBehaviourKind kind Source #

Describes the behaviour common for entrypoints of given kind.

This has very special use cases, like contracts with mix of upgradeable and permanent entrypoints.

diEntrypointToMarkdown :: HeaderLevel -> DEntrypoint level -> Markdown Source #

Default implementation of docItemToMarkdown for entrypoints.

data SomeEntrypointArg Source #

Entrypoint argument type in typed representation.

Constructors

forall a.(NiceParameter a, TypeHasDoc a) => SomeEntrypointArg (Proxy a) 

data DEntrypointArg Source #

Describes argument of an entrypoint.

Constructors

DEntrypointArg 

Fields

  • epaArg :: Maybe SomeEntrypointArg

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

  • 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 opposite to one in which they are given. E.g. suppose that an entrypoint is called as Run (Service1 arg); then the first step (actual last) should describe wrapping into Run constructor, and the second step (actual first) should be about wrapping into Service1 constructor.

data DType where #

Constructors

DType :: forall a. TypeHasDoc a => Proxy a -> DType 

Instances

Instances details
Eq DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

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

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

Ord DType 
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 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

DocItem DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DType :: DocItemPlacementKind #

type DocItemReferenced DType :: DocItemReferencedKind #

type DocItemPlacement DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemReferenced DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

Pick a type documentation from CtorField.

Instances

Instances details
KnownSymbol con => DeriveCtorFieldDoc con 'NoFields Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

(NiceParameter ty, TypeHasDoc ty, KnownValue ty, KnownSymbol con) => DeriveCtorFieldDoc con ('OneField ty) Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

newtype ParamBuilder Source #

When describing the way of parameter construction - piece of incremental builder for this description.

Constructors

ParamBuilder 

Fields

  • unParamBuilder :: Markdown -> Markdown

    Argument stands for previously constructed parameter piece, and returned value - a piece constructed after our step.

Instances

Instances details
Eq ParamBuilder Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Show ParamBuilder Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Buildable ParamBuilder Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

data ParamBuildingDesc Source #

Constructors

ParamBuildingDesc 

Fields

data ParamBuildingStep Source #

Describes a parameter building step.

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

Constructors

PbsWrapIn Text ParamBuildingDesc

Wraps something into constructor with given name. Constructor should be the one which corresponds to an entrypoint defined via field annotation, for more complex cases use PbsCustom.

PbsCallEntrypoint EpName

Directly call an entrypoint marked with a field annotation.

PbsCustom ParamBuildingDesc

Other action.

PbsUncallable [ParamBuildingStep]

This entrypoint cannot be called, which is possible when an explicit default entrypoint is present. This is not a true entrypoint but just some intermediate node in or tree and neither it nor any of its parents are marked with a field annotation.

It contains dummy ParamBuildingSteps which were assigned before entrypoints were taken into account.

mkPbsWrapIn :: Text -> ParamBuilder -> ParamBuildingStep Source #

Make a ParamBuildingStep that tells about wrapping an argument into a constructor with given name and uses given ParamBuilder as description of Michelson part.

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 :: forall (x :: T). SingI x => Notes x -> Ty #

mkDEpUType :: forall t. (KnownValue t, HasAnnotation t) => Ty 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), NiceParameter param, TypeHasDoc 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, 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 a parameter or its part.

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

finalizeParamCallingDoc :: forall cp inp out. (NiceParameterFull cp, RequireSumType cp, HasCallStack) => ((cp ': inp) :-> out) -> (cp ': inp) :-> out Source #

Version of 'finalizeParamCallingDoc'' more convenient for manual call in a contract.

finalizeParamCallingDoc' :: forall cp inp out. (NiceParameterFull cp, HasCallStack) => Proxy cp -> (inp :-> out) -> inp :-> out Source #

Modify param building steps with respect to entrypoints that given parameter declares.

Each contract with entrypoints should eventually call this function, otherwise, in case if contract uses built-in entrypoints feature, the resulting parameter building steps in the generated documentation will not consider entrypoints and thus may be incorrect.

Calling this twice over the same code is also prohibited.

This method is for internal use, if you want to apply it to a contract manually, use finalizeParamCallingDoc.

areFinalizedParamBuildingSteps :: [ParamBuildingStep] -> Bool Source #

Whether finalizeParamCallingDoc has already been applied to these steps.

entryCaseSimple_ :: forall cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints PlainEntrypointsKind cp, RequireFlatParamEps cp) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp ': inp) :-> out Source #

entryCaseSimple :: forall cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints PlainEntrypointsKind cp, RequireFlatParamEps cp) => IsoRecTuple clauses -> (cp ': inp) :-> out Source #

Version of entryCase for contracts with flat parameter, use it when you need only one entryCase all over the contract implementation.

type family RequireFlatEpDerivation cp deriv :: Constraint where ... Source #

Equations

RequireFlatEpDerivation _ EpdNone = () 
RequireFlatEpDerivation _ EpdPlain = () 
RequireFlatEpDerivation cp deriv = TypeError (('Text "Parameter is not flat" :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")) :$$: (('Text "With entrypoints derivation way `" :<>: 'ShowType deriv) :<>: 'Text "`"))