| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Lorentz.Entrypoints.Doc
Description
Utilities for declaring and documenting entry points.
Synopsis
- data DEntrypoint (kind :: Type) = DEntrypoint {}
- pattern DEntrypointDocItem :: DEntrypoint kind -> SomeDocItem
- class Typeable ep => EntrypointKindHasDoc (ep :: Type) where
- entrypointSection :: EntrypointKindHasDoc kind => Text -> Proxy kind -> (i :-> o) -> i :-> o
- data DEntrypointReference = DEntrypointReference Text Anchor
- class EntryArrow kind name body where
- data PlainEntrypointsKind
- type FlattenedEntrypointsKind = FlattenedEntrypointsKindHiding '[]
- data FlattenedEntrypointsKindHiding (hiddenEntrypoints :: [Symbol])
- data CommonContractBehaviourKind
- data CommonEntrypointsBehaviourKind kind
- diEntrypointToMarkdown :: HeaderLevel -> DEntrypoint level -> Markdown
- data SomeEntrypointArg = forall a.(NiceParameter a, TypeHasDoc a) => SomeEntrypointArg (Proxy a)
- data DEntrypointArg = DEntrypointArg {}
- data DType where
- DType :: forall a. TypeHasDoc a => Proxy a -> DType
- class KnownSymbol con => DeriveCtorFieldDoc con (cf :: CtorField) where
- newtype ParamBuilder = ParamBuilder {
- unParamBuilder :: Markdown -> Markdown
- data ParamBuildingDesc = ParamBuildingDesc {}
- data ParamBuildingStep
- mkPbsWrapIn :: Text -> ParamBuilder -> ParamBuildingStep
- clarifyParamBuildingSteps :: ParamBuildingStep -> (inp :-> out) -> inp :-> out
- emptyDEpArg :: DEntrypointArg
- mkUType :: forall (x :: T). Notes x -> Ty
- mkDEpUType :: forall t. HasAnnotation t => Ty
- mkDEntrypointArgSimple :: forall t. (NiceParameter t, TypeHasDoc t) => DEntrypointArg
- type DocumentEntrypoints kind a = (Generic a, GDocumentEntrypoints (BuildEPTree' a) kind (GRep a) '[])
- documentEntrypoint :: forall kind epName param s out. (KnownSymbol epName, DocItem (DEntrypoint kind), NiceParameter param, TypeHasDoc param) => ((param : s) :-> out) -> (param : s) :-> out
- entryCase :: forall dt entrypointKind out inp clauses. (CaseTC dt out inp clauses, DocumentEntrypoints entrypointKind dt) => Proxy entrypointKind -> IsoRecTuple clauses -> (dt : inp) :-> out
- 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
- finalizeParamCallingDoc :: forall cp inp out. (NiceParameterFull cp, RequireSumType cp, HasCallStack) => ((cp : inp) :-> out) -> (cp : inp) :-> out
- finalizeParamCallingDoc' :: forall cp inp out. (NiceParameterFull cp, HasCallStack) => Proxy cp -> (inp :-> out) -> inp :-> out
- areFinalizedParamBuildingSteps :: [ParamBuildingStep] -> Bool
- entryCaseSimple_ :: forall cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints PlainEntrypointsKind cp, RequireFlatParamEps cp) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp : inp) :-> out
- entryCaseSimple :: forall cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints PlainEntrypointsKind cp, RequireFlatParamEps cp) => IsoRecTuple clauses -> (cp : inp) :-> out
- entryCaseFlattened_ :: forall cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints FlattenedEntrypointsKind cp) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp : inp) :-> out
- entryCaseFlattened :: forall cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints FlattenedEntrypointsKind cp) => IsoRecTuple clauses -> (cp : inp) :-> out
- entryCaseFlattenedHiding_ :: forall heps cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints (FlattenedEntrypointsKindHiding heps) cp, HasEntrypoints (ParameterEntrypointsDerivation cp) cp heps) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp : inp) :-> out
- entryCaseFlattenedHiding :: forall heps cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints (FlattenedEntrypointsKindHiding heps) cp, HasEntrypoints (ParameterEntrypointsDerivation cp) cp heps) => IsoRecTuple clauses -> (cp : inp) :-> out
- type family RequireFlatParamEps cp :: Constraint where ...
- type family RequireFlatEpDerivation cp deriv :: Constraint where ...
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 | |
Instances
| EntrypointKindHasDoc ep => DocItem (DEntrypoint ep) Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type DocItemPlacement (DEntrypoint ep) :: DocItemPlacementKind # type DocItemReferenced (DEntrypoint ep) :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DEntrypoint ep -> DocItemRef (DocItemPlacement (DEntrypoint ep)) (DocItemReferenced (DEntrypoint ep)) # docItemToMarkdown :: HeaderLevel -> DEntrypoint ep -> Markdown # docItemToToc :: HeaderLevel -> DEntrypoint ep -> Markdown # docItemDependencies :: DEntrypoint ep -> [SomeDocDefinitionItem] # docItemsOrder :: [DEntrypoint ep] -> [DEntrypoint ep] # | |
| type DocItemPlacement (DEntrypoint ep) Source # | |
Defined in Lorentz.Entrypoints.Doc | |
| type DocItemReferenced (DEntrypoint ep) Source # | |
Defined in Lorentz.Entrypoints.Doc | |
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
entrypointKindOverrideSpecified | entrypointKindPos, entrypointKindSectionName
Associated Types
type EntrypointKindOverride ep Source #
Can be used to make a kind equivalent to some other kind;
if changing this, entrypointKindPos and entrypointKindSectionName
will be ignored.
type EntrypointKindOverride ep = ep
Methods
entrypointKindOverrideSpecified :: Dict ((EntrypointKindOverride ep == ep) ~ False) Source #
Warning: Normally you should never need to use this function
Implement this when specifying EntrypointKindOverride.
This should never be normally used, but because MINIMAL pragma
can't specify type families, we use this hack.
Default implementation is a bottom (i.e. a runtime error).
If implemented, it should be
entrypointKindOverrideSpecified = Dict
entrypointKindPos :: Natural Source #
Position of the respective entrypoints section in the doc. This shares the same positions space with all other doc items.
default entrypointKindPos :: EntrypointKindHasDoc (EntrypointKindOverride ep) => Natural Source #
entrypointKindSectionName :: Text Source #
Name of the respective entrypoints section.
default entrypointKindSectionName :: EntrypointKindHasDoc (EntrypointKindOverride ep) => Text Source #
entrypointKindSectionDescription :: Maybe Markdown Source #
Description in the respective entrypoints section.
Instances
| EntrypointKindHasDoc CommonContractBehaviourKind Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride CommonContractBehaviourKind Source # | |
| EntrypointKindHasDoc PlainEntrypointsKind Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types | |
| Typeable heps => EntrypointKindHasDoc (FlattenedEntrypointsKindHiding heps) Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride (FlattenedEntrypointsKindHiding heps) Source # | |
| EntrypointKindHasDoc kind => EntrypointKindHasDoc (CommonEntrypointsBehaviourKind kind) Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride (CommonEntrypointsBehaviourKind kind) Source # | |
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.
data DEntrypointReference Source #
Inserts a reference to an existing entrypoint.
This helps to avoid duplication in the generated documentation, in order not to overwhelm the reader.
Constructors
| DEntrypointReference Text Anchor |
Instances
| DocItem DEntrypointReference Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type DocItemPlacement DEntrypointReference :: DocItemPlacementKind # type DocItemReferenced DEntrypointReference :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DEntrypointReference -> DocItemRef (DocItemPlacement DEntrypointReference) (DocItemReferenced DEntrypointReference) # docItemToMarkdown :: HeaderLevel -> DEntrypointReference -> Markdown # docItemToToc :: HeaderLevel -> DEntrypointReference -> Markdown # docItemDependencies :: DEntrypointReference -> [SomeDocDefinitionItem] # docItemsOrder :: [DEntrypointReference] -> [DEntrypointReference] # | |
| type DocItemPlacement DEntrypointReference Source # | |
Defined in Lorentz.Entrypoints.Doc | |
| type DocItemReferenced DEntrypointReference Source # | |
Defined in Lorentz.Entrypoints.Doc | |
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), NiceParameter param, TypeHasDoc param, KnownValue param) => EntryArrow (kind :: Type) name body Source # | |
data PlainEntrypointsKind Source #
Default value for DEntrypoint type argument.
Instances
| EntrypointKindHasDoc PlainEntrypointsKind Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types | |
| type EntrypointKindOverride PlainEntrypointsKind Source # | |
type FlattenedEntrypointsKind = FlattenedEntrypointsKindHiding '[] Source #
A convenience type synonym for FlattenedEntrypointsKindHiding not hiding
any entrypoitns.
data FlattenedEntrypointsKindHiding (hiddenEntrypoints :: [Symbol]) Source #
Special entrypoint kind that flattens one level of recursive entrypoints.
With EpdRecursive, intermediary nodes are hidden from documentation.
With EpdDelegate, intermediary nodes will still be shown.
Any entrypoints can be omitted from docs by listing those in the type
parameter (which is especially helpful with EpdDelegate).
For other entrypoint derivation strategies (e.g. EpdPlain), behaves like
PlainEntrypointsKind (with the exception of hiding entrypoints from docs)
If you have several levels of recursion, each level will need to have this kind.
Note that list of entrypoints to be hidden is not checked by default. Use
entryCaseFlattenedHiding to have a static check that entrypoints to be
hidden do indeed exist.
Instances
| Typeable heps => EntrypointKindHasDoc (FlattenedEntrypointsKindHiding heps) Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride (FlattenedEntrypointsKindHiding heps) Source # | |
| type EntrypointKindOverride (FlattenedEntrypointsKindHiding heps) Source # | |
Defined in Lorentz.Entrypoints.Doc | |
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).
Instances
| EntrypointKindHasDoc CommonContractBehaviourKind Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride CommonContractBehaviourKind Source # | |
| type EntrypointKindOverride CommonContractBehaviourKind Source # | |
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.
Instances
| EntrypointKindHasDoc kind => EntrypointKindHasDoc (CommonEntrypointsBehaviourKind kind) Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type EntrypointKindOverride (CommonEntrypointsBehaviourKind kind) Source # | |
| type EntrypointKindOverride (CommonEntrypointsBehaviourKind kind) Source # | |
Defined in Lorentz.Entrypoints.Doc type EntrypointKindOverride (CommonEntrypointsBehaviourKind kind) = CommonEntrypointsBehaviourKind kind | |
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
| |
Instances
| DocItem DEntrypointArg Source # | |
Defined in Lorentz.Entrypoints.Doc Associated Types type DocItemPlacement DEntrypointArg :: DocItemPlacementKind # type DocItemReferenced DEntrypointArg :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DEntrypointArg -> DocItemRef (DocItemPlacement DEntrypointArg) (DocItemReferenced DEntrypointArg) # docItemToMarkdown :: HeaderLevel -> DEntrypointArg -> Markdown # docItemToToc :: HeaderLevel -> DEntrypointArg -> Markdown # docItemDependencies :: DEntrypointArg -> [SomeDocDefinitionItem] # docItemsOrder :: [DEntrypointArg] -> [DEntrypointArg] # | |
| type DocItemPlacement DEntrypointArg Source # | |
Defined in Lorentz.Entrypoints.Doc | |
| type DocItemReferenced DEntrypointArg Source # | |
Defined in Lorentz.Entrypoints.Doc | |
Constructors
| DType :: forall a. TypeHasDoc a => Proxy a -> DType |
Instances
| Eq DType | |
| Ord DType | |
| DocItem DType | |
Defined in Morley.Michelson.Typed.Haskell.Doc Associated Types type DocItemPlacement DType :: DocItemPlacementKind # type DocItemReferenced DType :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DType -> DocItemRef (DocItemPlacement DType) (DocItemReferenced DType) # docItemToMarkdown :: HeaderLevel -> DType -> Markdown # docItemToToc :: HeaderLevel -> DType -> Markdown # docItemDependencies :: DType -> [SomeDocDefinitionItem] # docItemsOrder :: [DType] -> [DType] # | |
| Buildable DType | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
| type DocItemPlacement DType | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
| type DocItemReferenced DType | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
class KnownSymbol con => DeriveCtorFieldDoc con (cf :: CtorField) where Source #
Pick a type documentation from CtorField.
Methods
Instances
| KnownSymbol con => DeriveCtorFieldDoc con 'NoFields Source # | |
Defined in Lorentz.Entrypoints.Doc Methods | |
| (NiceParameter ty, TypeHasDoc ty, KnownValue ty, KnownSymbol con) => DeriveCtorFieldDoc con ('OneField ty) Source # | |
Defined in Lorentz.Entrypoints.Doc Methods | |
newtype ParamBuilder Source #
When describing the way of parameter construction - piece of incremental builder for this description.
Constructors
| ParamBuilder | |
Fields
| |
Instances
| Buildable ParamBuilder Source # | |
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 |
| 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 It contains dummy |
Instances
| Buildable ParamBuildingStep Source # | |
Defined in Lorentz.Entrypoints.Doc | |
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.
mkDEpUType :: forall t. HasAnnotation t => Ty Source #
mkDEntrypointArgSimple :: forall t. (NiceParameter t, TypeHasDoc t) => DEntrypointArg Source #
type DocumentEntrypoints kind a = (Generic a, GDocumentEntrypoints (BuildEPTree' a) kind (GRep 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 #
Version of entryCase_ for contracts with flat parameter.
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.
entryCaseFlattened_ :: forall cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints FlattenedEntrypointsKind cp) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp : inp) :-> out Source #
Version of entryCase_ for contracts with recursive parameter that needs
to be flattened. Use it with EpdRecursive when you don't need intermediary
nodes in autodoc.
entryCaseFlattened :: forall cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints FlattenedEntrypointsKind cp) => IsoRecTuple clauses -> (cp : inp) :-> out Source #
Version of entryCase for contracts with recursive parameter that needs
to be flattened. Use it with EpdRecursive when you don't need intermediary
nodes in autodoc.
entryCaseFlattenedHiding_ :: forall heps cp out inp. (InstrCaseC cp, RMap (CaseClauses cp), DocumentEntrypoints (FlattenedEntrypointsKindHiding heps) cp, HasEntrypoints (ParameterEntrypointsDerivation cp) cp heps) => Rec (CaseClauseL inp out) (CaseClauses cp) -> (cp : inp) :-> out Source #
Version of entryCase_ for contracts with recursive delegate parameter that needs
to be flattened. Use it with EpdDelegate when you don't need hierarchical
entrypoints in autodoc. You can also hide particular entrypoints with the
type parameter. Consider using entryCaseFlattened_ if you don't want
to hide any entrypoints.
entryCaseFlattenedHiding :: forall heps cp out inp clauses. (CaseTC cp out inp clauses, DocumentEntrypoints (FlattenedEntrypointsKindHiding heps) cp, HasEntrypoints (ParameterEntrypointsDerivation cp) cp heps) => IsoRecTuple clauses -> (cp : inp) :-> out Source #
Version of entryCase for contracts with recursive delegate parameter that needs
to be flattened. Use it with EpdDelegate when you don't need hierarchical
entrypoints in autodoc. You can also hide particular entrypoints with the
first type parameter. Consider using entryCaseFlattened if you don't want
to hide any entrypoints.
entryCaseFlattenedHiding @'[Ep1, Ep2] ...
type family RequireFlatParamEps cp :: Constraint where ... Source #
Equations
| RequireFlatParamEps cp = (NiceParameterFull cp, RequireFlatEpDerivation cp (GetParameterEpDerivation cp), RequireSumType cp) |
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 "`")) |