lorentz-0.4.0: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Doc

Synopsis

Documentation

doc :: DocItem di => di -> s :-> s Source #

Put a document item.

docGroup :: DocGrouping -> (inp :-> out) -> inp :-> out Source #

Group documentation built in the given piece of code into block dedicated to one thing, e.g. to one entrypoint.

docStorage :: forall storage s. TypeHasDoc storage => s :-> s Source #

Insert documentation of the contract storage type. The type should be passed using type applications.

contractName :: Text -> (inp :-> out) -> inp :-> out Source #

Give a name to given contract. Apply it to the whole contract code.

contractGeneral :: (inp :-> out) -> inp :-> out Source #

Takes an instruction that inserts documentation items with general information about the contract. Inserts it into general section. See DGeneralInfoSection.

contractGeneralDefault :: s :-> s Source #

Inserts general information about the contract using the default format.

Currently we only include git revision. It is unknown in the library code and is supposed to be updated in an executable.

cutLorentzNonDoc :: (inp :-> out) -> s :-> s Source #

Leave only instructions related to documentation.

This function is useful when your method executes a lambda coming from outside, but you know its properties and want to propagate its documentation to your contract code.

Re-exports

type Markdown = Builder #

A piece of markdown document.

This is opposed to Text type, which in turn is not supposed to contain markup elements.

class (Typeable d, DOrd d, KnownNat (DocItemPosition d)) => DocItem d where #

A piece of documentation describing one property of a thing, be it a name or description of a contract, or an error throwable by given endpoint.

Items of the same type appear close to each other in a rendered documentation and form a section.

Doc items are later injected into a contract code via a dedicated nop-like instruction. Normally doc items which belong to one section appear in resulting doc in the same order in which they appeared in the contract.

While documentation framework grows, this typeclass acquires more and more methods for fine tuning of existing rendering logic because we don't want to break backward compatibility, hope one day we will make everything concise :( E.g. all rendering and reording stuff could be merged in one method, and we could have several template implementations for it which would allow user to specify only stuff relevant to his case.

Minimal complete definition

docItemSectionName, docItemToMarkdown

Associated Types

type DocItemPosition d = (pos :: Nat) | pos -> d #

Position of this item in the resulting documentation; the smaller the value, the higher the section with this element will be placed.

Documentation structure is not necessarily flat. If some doc item consolidates a whole documentation block within it, this block will have its own placement of items independent from outer parts of the doc.

type DocItemPlacement d :: DocItemPlacementKind #

Defines where given doc item should be put. There are two options: 1. Inline right here (default behaviour); 2. Put into definitions section.

Note that we require all doc items with "in definitions" placement to have Eq and Ord instances which comply the following law: if two documentation items describe the same entity or property, they should be considered equal.

Methods

docItemSectionName :: Maybe Text #

When multiple items of the same type belong to one section, how this section will be called.

If not provided, section will contain just untitled content.

docItemSectionDescription :: Maybe Markdown #

Description of a section.

Can be used to mention some common things about all elements of this section. Markdown syntax is permitted here.

docItemSectionNameStyle :: DocSectionNameStyle #

How to render section name.

Takes effect only if section name is set.

docItemRef :: d -> DocItemRef (DocItemPlacement d) #

Defines a function which constructs an unique identifier of given doc item, if it has been decided to put the doc item into definitions section.

Identifier should be unique both among doc items of the same type and items of other types. Thus, consider using "typeId-contentId" pattern.

docItemToMarkdown :: HeaderLevel -> d -> Markdown #

Render given doc item to Markdown, preferably one line, optionally with header.

Accepts the smallest allowed level of header. (Using smaller value than provided one will interfere with existing headers thus delivering mess).

docItemDependencies :: d -> [SomeDocDefinitionItem] #

All doc items which this doc item refers to.

They will automatically be put to definitions as soon as given doc item is detected.

docItemsOrder :: [d] -> [d] #

This function accepts doc items put under the same section in the order in which they appeared in the contract and returns their new desired order. It's also fine to use this function for filtering or merging doc items.

Default implementation * leaves inlined items as is; * for items put to definitions, lexicographically sorts them by their id.

Instances

Instances details
DocItem DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPosition DType = (pos :: Nat) #

type DocItemPlacement DType :: DocItemPlacementKind #

DocItem DStorageType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

DocItem DGeneralInfoSection 
Instance details

Defined in Michelson.Doc

DocItem DName 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPosition DName = (pos :: Nat) #

type DocItemPlacement DName :: DocItemPlacementKind #

DocItem DDescription 
Instance details

Defined in Michelson.Doc

DocItem DGitRevision 
Instance details

Defined in Michelson.Doc

DocItem DComment 
Instance details

Defined in Michelson.Doc

DocItem DAnchor 
Instance details

Defined in Michelson.Doc

DocItem DUStoreTemplate Source # 
Instance details

Defined in Lorentz.UStore.Doc

DocItem DThrows Source # 
Instance details

Defined in Lorentz.Errors

DocItem DError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type DocItemPosition DError = (pos :: Nat) #

type DocItemPlacement DError :: DocItemPlacementKind #

DocItem DMigrationActionDesc Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

DocItem DDescribeErrorTagMap Source # 
Instance details

Defined in Lorentz.Errors.Numeric.Doc

DocItem DEntryPointArg Source # 
Instance details

Defined in Lorentz.EntryPoints.Doc

DocItem DEntryPointReference Source # 
Instance details

Defined in Lorentz.EntryPoints.Doc

DocItem (DEntryPoint PlainEntryPointsKind) Source # 
Instance details

Defined in Lorentz.EntryPoints.Doc

docItemPosition :: DocItem d => DocItemPos #

Get doc item position at term-level.

newtype DocItemId #

Some unique identifier of a doc item.

All doc items which should be refer-able need to have this identifier.

Constructors

DocItemId Text 

Instances

Instances details
Eq DocItemId 
Instance details

Defined in Michelson.Doc

Ord DocItemId 
Instance details

Defined in Michelson.Doc

Show DocItemId 
Instance details

Defined in Michelson.Doc

ToAnchor DocItemId 
Instance details

Defined in Michelson.Doc

Methods

toAnchor :: DocItemId -> Anchor #

data DocItemPlacementKind #

Where do we place given doc item.

Constructors

DocItemInlined

Placed in the document content itself.

DocItemInDefinitions

Placed in dedicated definitions section; can later be referenced.

data DocItemRef (p :: DocItemPlacementKind) where #

Defines an identifier which given doc item can be referenced with.

Instances

Instances details
ToAnchor (DocItemRef 'DocItemInDefinitions) 
Instance details

Defined in Michelson.Doc

data DocSectionNameStyle #

How to render section name.

Constructors

DocSectionNameBig

Suitable for block name.

DocSectionNameSmall

Suitable for subsection title within block.

data SomeDocItem where #

Hides some documentation item.

Constructors

SomeDocItem :: forall d. DocItem d => d -> SomeDocItem 

Instances

Instances details
Show DocGrouping 
Instance details

Defined in Michelson.Doc

Show SomeDocItem

To automatically derive instance Show Michelson.Typed.Instr later.

Instance details

Defined in Michelson.Doc

NFData SomeDocItem 
Instance details

Defined in Michelson.Doc

Methods

rnf :: SomeDocItem -> () #

newtype SubDoc #

A part of documentation to be grouped. Essentially incapsulates DocBlock.

Constructors

SubDoc DocBlock 

Instances

Instances details
Show DocGrouping 
Instance details

Defined in Michelson.Doc

type DocGrouping = SubDoc -> SomeDocItem #

A function which groups a piece of doc under one doc item.

data ContractDoc #

Keeps documentation gathered for some piece of contract code.

Used for building documentation of a contract.

Constructors

ContractDoc 

Fields

  • cdContents :: DocBlock

    All inlined doc items.

  • cdDefinitions :: DocBlock

    Definitions used in document.

    Usually you put some large and repetitive descriptions here. This differs from the document content in that it contains sections which are always at top-level, disregard the nesting.

    All doc items which define docItemId method go here, and only they.

  • cdDefinitionsSet :: Set SomeDocDefinitionItem

    We remember all already declared entries to avoid cyclic dependencies in documentation items discovery.

  • cdDefinitionIds :: Set DocItemId

    We remember all already used identifiers. (Documentation naturally should not declare multiple items with the same identifier because that would make references to the respective anchors ambiguous).

Instances

Instances details
Semigroup ContractDoc

Contract documentation assembly primarily relies on this instance.

Instance details

Defined in Michelson.Doc

Monoid ContractDoc 
Instance details

Defined in Michelson.Doc

newtype GitRepoSettings #

Repository settings for DGitRevision.

Constructors

GitRepoSettings 

Fields

mkDGitRevision :: ExpQ #

Make DGitRevision.

>>> :t $mkDGitRevision
GitRepoSettings -> DGitRevision

data DType where #

Doc element with description of a type.

Constructors

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

dTypeDep :: TypeHasDoc t => SomeDocDefinitionItem #

Create a DType in form suitable for putting to typeDocDependencies.

docDefinitionRef :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => Markdown -> d -> Markdown #

Make a reference to doc item in definitions.

contractDocToMarkdown :: ContractDoc -> LText #

Render given contract documentation to markdown document.

subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown #

Render documentation for SubDoc.

class (Typeable a, SingI (TypeDocFieldDescriptions a), FieldDescriptionsValid (TypeDocFieldDescriptions a) a) => TypeHasDoc a where #

Description for a Haskell type appearing in documentation.

Minimal complete definition

typeDocMdDescription

Associated Types

type TypeDocFieldDescriptions a :: FieldDescriptions #

Description of constructors and fields of a.

See FieldDescriptions documentation for an example of usage.

Descriptions will be checked at compile time to make sure that only existing constructors and fields are referenced.

For that check to work instance Generic a is required whenever TypeDocFieldDescriptions is not empty.

For implementation of the check see FieldDescriptionsValid type family.

Methods

typeDocName :: Proxy a -> Text #

Name of type as it appears in definitions section.

Each type must have its own unique name because it will be used in identifier for references.

Default definition derives name from Generics. If it does not fit, consider defining this function manually. (We tried using Data for this, but it produces names including module names which is not do we want).

typeDocMdDescription :: Markdown #

Explanation of a type. Markdown formatting is allowed.

typeDocMdReference :: Proxy a -> WithinParens -> Markdown #

How reference to this type is rendered, in Markdown.

Examples:

  • [Integer](#type-integer),
  • [Maybe](#type-Maybe) [()](#type-unit).

Consider using one of the following functions as default implementation; which one to use depends on number of type arguments in your type:

If none of them fits your purposes precisely, consider using customTypeDocMdReference.

typeDocDependencies :: Proxy a -> [SomeDocDefinitionItem] #

All types which this type directly contains.

Used in automatic types discovery.

typeDocHaskellRep :: TypeDocHaskellRep a #

For complex types - their immediate Haskell representation.

For primitive types set this to Nothing.

For homomorphic types use homomorphicTypeDocHaskellRep implementation.

For polymorhpic types consider using concreteTypeDocHaskellRep as implementation.

Modifier haskellRepNoFields can be used to hide names of fields, beneficial for newtypes.

Another modifier called haskellRepStripFieldPrefix can be used for datatypes to leave only meaningful part of name in every field.

typeDocMichelsonRep :: TypeDocMichelsonRep a #

Final michelson representation of a type.

For homomorphic types use homomorphicTypeDocMichelsonRep implementation.

For polymorhpic types consider using concreteTypeDocMichelsonRep as implementation.

Instances

Instances details
TypeHasDoc Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc () 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions () :: FieldDescriptions #

TypeHasDoc ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Operation 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc MText 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Empty Source # 
Instance details

Defined in Lorentz.Empty

PolyTypeHasDocC '[a] => TypeHasDoc [a] 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions [a] :: FieldDescriptions #

PolyTypeHasDocC '[a] => TypeHasDoc (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyCTypeHasDocC '[a] => TypeHasDoc (Set a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Set a) :: FieldDescriptions #

PolyTypeHasDocC '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

UStoreTemplateHasDoc template => TypeHasDoc (UStore template) Source # 
Instance details

Defined in Lorentz.UStore.Doc

Associated Types

type TypeDocFieldDescriptions (UStore template) :: FieldDescriptions #

(TypeHasDoc r, IsError (VoidResult r)) => TypeHasDoc (VoidResult r) Source # 
Instance details

Defined in Lorentz.Macro

Typeable interface => TypeHasDoc (UParam interface) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type TypeDocFieldDescriptions (UParam interface) :: FieldDescriptions #

PolyTypeHasDocC '[l, r] => TypeHasDoc (Either l r) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Either l r) :: FieldDescriptions #

PolyTypeHasDocC '[a, b] => TypeHasDoc (a, b) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b) :: FieldDescriptions #

(PolyCTypeHasDocC '[k], PolyTypeHasDocC '[v], Ord k) => TypeHasDoc (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Map k v) :: FieldDescriptions #

(PolyCTypeHasDocC '[k], PolyTypeHasDocC '[v], Ord k) => TypeHasDoc (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (BigMap k v) :: FieldDescriptions #

Each '[Typeable :: [Type] -> Constraint, ReifyList TypeHasDoc] '[i, o] => TypeHasDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (i :-> o) :: FieldDescriptions #

Each '[Typeable :: Type -> Constraint, UStoreTemplateHasDoc] '[oldStore, newStore] => TypeHasDoc (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type TypeDocFieldDescriptions (MigrationScript oldStore newStore) :: FieldDescriptions #

Each '[Typeable :: Type -> Constraint, TypeHasDoc] '[a, r] => TypeHasDoc (Void_ a r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (Void_ a r) :: FieldDescriptions #

Each '[Typeable :: Type -> Constraint, TypeHasDoc] '[a, r] => TypeHasDoc (View a r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (View a r) :: FieldDescriptions #

(ExtensibleHasDoc x, ReifyList DocumentCtor (EnumerateCtors (GetCtors x))) => TypeHasDoc (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

PolyTypeHasDocC '[a, b, c] => TypeHasDoc (a, b, c) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b, c) :: FieldDescriptions #

(TypeHasDoc (ApplyNamedFunctor f a), KnownSymbol n, SingI (ToT (ApplyNamedFunctor f Integer)), Typeable f, Typeable a) => TypeHasDoc (NamedF f a n) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (NamedF f a n) :: FieldDescriptions #

PolyTypeHasDocC '[a, b, c, d] => TypeHasDoc (a, b, c, d) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b, c, d) :: FieldDescriptions #

PolyTypeHasDocC '[a, b, c, d, e] => TypeHasDoc (a, b, c, d, e) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b, c, d, e) :: FieldDescriptions #

PolyTypeHasDocC '[a, b, c, d, e, f] => TypeHasDoc (a, b, c, d, e, f) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b, c, d, e, f) :: FieldDescriptions #

Methods

typeDocName :: Proxy (a, b, c, d, e, f) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (a, b, c, d, e, f) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (a, b, c, d, e, f) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (a, b, c, d, e, f) #

typeDocMichelsonRep :: TypeDocMichelsonRep (a, b, c, d, e, f) #

PolyTypeHasDocC '[a, b, c, d, e, f, g] => TypeHasDoc (a, b, c, d, e, f, g) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b, c, d, e, f, g) :: FieldDescriptions #

Methods

typeDocName :: Proxy (a, b, c, d, e, f, g) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (a, b, c, d, e, f, g) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (a, b, c, d, e, f, g) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (a, b, c, d, e, f, g) #

typeDocMichelsonRep :: TypeDocMichelsonRep (a, b, c, d, e, f, g) #

data SomeTypeWithDoc where #

Data hides some type implementing TypeHasDoc.

Constructors

SomeTypeWithDoc :: forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc 

class HaveCommonTypeCtor (a :: k) (b :: k1) #

Require two types to be built from the same type constructor.

E.g. HaveCommonTypeCtor (Maybe Integer) (Maybe Natural) is defined, while HaveCmmonTypeCtor (Maybe Integer) [Integer] is not.

Instances

Instances details
HaveCommonTypeCtor (a :: k) (a :: k) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

HaveCommonTypeCtor ac bc => HaveCommonTypeCtor (ac a :: k2) (bc b :: k4) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

class IsHomomorphic (a :: k) #

Require this type to be homomorphic.

Instances

Instances details
IsHomomorphic (a :: k) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

(TypeError ('Text "Type is not homomorphic: " :<>: 'ShowType (a b)) :: Constraint) => IsHomomorphic (a b :: k2) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

genericTypeDocDependencies :: (Generic a, GTypeHasDoc (Rep a)) => Proxy a -> [SomeDocDefinitionItem] #

Implement typeDocDependencies via getting all immediate fields of a datatype.

Note: this will not include phantom types, I'm not sure yet how this scenario should be handled (@martoon).

customTypeDocMdReference :: (Text, DType) -> [DType] -> WithinParens -> Markdown #

Render a reference to a type which consists of type constructor (you have to provide name of this type constructor and documentation for the whole type) and zero or more type arguments.

poly1TypeDocMdReference :: forall (t :: Type -> Type) r a. (r ~ t a, Typeable t, Each '[TypeHasDoc] '[r, a], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown #

Derive typeDocMdReference, for polymorphic type with one type argument, like Maybe Integer.

poly2TypeDocMdReference :: forall (t :: Type -> Type -> Type) r a b. (r ~ t a b, Typeable t, Each '[TypeHasDoc] '[r, a, b], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown #

Derive typeDocMdReference, for polymorphic type with two type arguments, like Lambda Integer Natural.

homomorphicTypeDocHaskellRep :: (Generic a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep a #

Implement typeDocHaskellRep for a homomorphic type.

Note that it does not require your type to be of IsHomomorphic instance, which can be useful for some polymorhpic types which, for documentation purposes, we want to consider homomorphic.

Example: Operation is in fact polymorhpic, but we don't want this fact to be reflected in the documentation.

concreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b #

Implement typeDocHaskellRep on example of given concrete type.

This is a best effort attempt to implement typeDocHaskellRep for polymorhpic types, as soon as there is no simple way to preserve type variables when automatically deriving Haskell representation of a type.

concreteTypeDocHaskellRepUnsafe :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep b #

Version of concreteTypeDocHaskellRep which does not ensure whether the type for which representation is built is any similar to the original type which you implement a TypeHasDoc instance for.

haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a #

Erase fields from Haskell datatype representation.

Use this when rendering fields names is undesired.

haskellRepStripFieldPrefix :: HasCallStack => TypeDocHaskellRep a -> TypeDocHaskellRep a #

Cut fields prefixes which we use according to the style guide.

E.g. cmMyField field will be transformed to myField.

concreteTypeDocMichelsonRep :: forall k a (b :: k). (Typeable a, SingI (ToT a), HaveCommonTypeCtor b a) => TypeDocMichelsonRep b #

Implement typeDocMichelsonRep on example of given concrete type.

This function exists for the same reason as concreteTypeDocHaskellRep.

concreteTypeDocMichelsonRepUnsafe :: forall k a (b :: k). (Typeable a, SingI (ToT a)) => TypeDocMichelsonRep b #

Version of concreteTypeDocHaskellRepUnsafe which does not ensure whether the type for which representation is built is any similar to the original type which you implement a TypeHasDoc instance for.

Orphan instances