Safe Haskell | None |
---|---|
Language | Haskell2010 |
Renderable documentation injected to contract code.
Synopsis
- class (Typeable d, DOrd d) => DocItem d where
- type DocItemPlacement d :: DocItemPlacementKind
- type DocItemReferenced d :: DocItemReferencedKind
- docItemPos :: Natural
- docItemSectionName :: Maybe Text
- docItemSectionDescription :: Maybe Markdown
- docItemSectionNameStyle :: DocSectionNameStyle
- docItemRef :: d -> DocItemRef (DocItemPlacement d) (DocItemReferenced d)
- docItemToMarkdown :: HeaderLevel -> d -> Markdown
- docItemToToc :: HeaderLevel -> d -> Markdown
- docItemDependencies :: d -> [SomeDocDefinitionItem]
- docItemsOrder :: [d] -> [d]
- docItemPosition :: forall d. DocItem d => DocItemPos
- newtype DocItemId = DocItemId Text
- data DocItemPlacementKind
- newtype DocItemPos = DocItemPos (Natural, Text)
- data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where
- type DocItemReferencedKind = Bool
- data DocSectionNameStyle
- data SomeDocItem where
- SomeDocItem :: DocItem d => d -> SomeDocItem
- data SomeDocDefinitionItem where
- SomeDocDefinitionItem :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem
- data DocElem d = DocElem {}
- data DocSection = forall d.DocItem d => DocSection (NonEmpty $ DocElem d)
- type DocBlock = Map DocItemPos DocSection
- newtype SubDoc = SubDoc DocBlock
- data ContractDoc = ContractDoc {}
- type DocGrouping = SubDoc -> SomeDocItem
- cdContentsL :: Lens' ContractDoc DocBlock
- cdDefinitionsL :: Lens' ContractDoc DocBlock
- cdDefinitionsSetL :: Lens' ContractDoc (Set SomeDocDefinitionItem)
- cdDefinitionIdsL :: Lens' ContractDoc (Set DocItemId)
- deIsAtomic :: DocElem d -> Bool
- subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown
- docItemToBlock :: forall di. DocItem di => di -> DocBlock
- lookupDocBlockSection :: forall d. DocItem d => DocBlock -> Maybe (NonEmpty d)
- contractDocToMarkdown :: ContractDoc -> LText
- contractDocToToc :: ContractDoc -> Markdown
- docGroupContent :: DocGrouping -> ContractDoc -> ContractDoc
- docDefinitionRef :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => Markdown -> d -> Markdown
- mdTocFromRef :: (DocItem d, DocItemReferenced d ~ 'True) => HeaderLevel -> Markdown -> d -> Markdown
- newtype DGeneralInfoSection = DGeneralInfoSection SubDoc
- data DName = DName Text SubDoc
- data DDescription = DDescription Markdown
- data DGitRevision
- = DGitRevisionKnown DGitRevisionInfo
- | DGitRevisionUnknown
- newtype GitRepoSettings = GitRepoSettings {
- grsMkGitRevision :: Text -> Text
- mkDGitRevision :: ExpQ
- morleyRepoSettings :: GitRepoSettings
- data DComment = DComment Text
- data DAnchor = DAnchor Anchor
- data DToc = DToc Markdown
Documentation
class (Typeable d, DOrd d) => DocItem d where Source #
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.
type DocItemPlacement d :: DocItemPlacementKind Source #
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.
type DocItemPlacement d = 'DocItemInlined Source #
type DocItemReferenced d :: DocItemReferencedKind Source #
type DocItemReferenced d = 'False Source #
docItemPos :: Natural Source #
Position of this item in the resulting documentation; the smaller the value, the higher the section with this element will be placed. If the position is the same as other doc items, they will be placed base on their name, alphabetically.
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.
docItemSectionName :: Maybe Text Source #
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 Source #
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 Source #
How to render section name.
Takes effect only if section name is set.
docItemRef :: d -> DocItemRef (DocItemPlacement d) (DocItemReferenced d) Source #
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.
default docItemRef :: (DocItemPlacement d ~ 'DocItemInlined, DocItemReferenced d ~ 'False) => d -> DocItemRef (DocItemPlacement d) (DocItemReferenced d) Source #
docItemToMarkdown :: HeaderLevel -> d -> Markdown Source #
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).
docItemToToc :: HeaderLevel -> d -> Markdown Source #
Render table of contents entry for given doc item to Markdown.
docItemDependencies :: d -> [SomeDocDefinitionItem] Source #
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] Source #
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
docItemPosition :: forall d. DocItem d => DocItemPos Source #
Get doc item position at term-level.
Some unique identifier of a doc item.
All doc items which should be refer-able need to have this identifier.
data DocItemPlacementKind Source #
Where do we place given doc item.
DocItemInlined | Placed in the document content itself. |
DocItemInDefinitions | Placed in dedicated definitions section; can later be referenced. |
newtype DocItemPos Source #
Position of all doc items of some type.
Instances
Eq DocItemPos Source # | |
Defined in Michelson.Doc (==) :: DocItemPos -> DocItemPos -> Bool # (/=) :: DocItemPos -> DocItemPos -> Bool # | |
Ord DocItemPos Source # | |
Defined in Michelson.Doc compare :: DocItemPos -> DocItemPos -> Ordering # (<) :: DocItemPos -> DocItemPos -> Bool # (<=) :: DocItemPos -> DocItemPos -> Bool # (>) :: DocItemPos -> DocItemPos -> Bool # (>=) :: DocItemPos -> DocItemPos -> Bool # max :: DocItemPos -> DocItemPos -> DocItemPos # min :: DocItemPos -> DocItemPos -> DocItemPos # | |
Show DocItemPos Source # | |
Defined in Michelson.Doc showsPrec :: Int -> DocItemPos -> ShowS # show :: DocItemPos -> String # showList :: [DocItemPos] -> ShowS # | |
Buildable DocItemPos Source # | |
Defined in Michelson.Doc build :: DocItemPos -> Builder # |
data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where Source #
DocItemRef :: DocItemId -> DocItemRef 'DocItemInDefinitions 'True | |
DocItemRefInlined :: DocItemId -> DocItemRef 'DocItemInlined 'True | |
DocItemNoRef :: DocItemRef 'DocItemInlined 'False |
Instances
ToAnchor (DocItemRef d 'True) Source # | |
Defined in Michelson.Doc |
type DocItemReferencedKind = Bool Source #
Type-level check whether or not a doc item can be referenced.
data DocSectionNameStyle Source #
How to render section name.
DocSectionNameBig | Suitable for block name. |
DocSectionNameSmall | Suitable for subsection title within block. |
data SomeDocItem where Source #
Hides some documentation item.
SomeDocItem :: DocItem d => d -> SomeDocItem |
Instances
Show SomeDocItem Source # | To automatically derive |
Defined in Michelson.Doc showsPrec :: Int -> SomeDocItem -> ShowS # show :: SomeDocItem -> String # showList :: [SomeDocItem] -> ShowS # | |
Show DocGrouping Source # | |
Defined in Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
NFData SomeDocItem Source # | |
Defined in Michelson.Doc rnf :: SomeDocItem -> () # |
data SomeDocDefinitionItem where Source #
Hides some documentation item which is put to "definitions" section.
SomeDocDefinitionItem :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem |
Instances
Eq SomeDocDefinitionItem Source # | |
Defined in Michelson.Doc (==) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (/=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # | |
Ord SomeDocDefinitionItem Source # | |
Defined in Michelson.Doc compare :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Ordering # (<) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (<=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (>) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (>=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # max :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> SomeDocDefinitionItem # min :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> SomeDocDefinitionItem # |
A doc item which we store, along with related information.
data DocSection Source #
Several doc items of the same type.
forall d.DocItem d => DocSection (NonEmpty $ DocElem d) |
Instances
Show DocSection Source # | |
Defined in Michelson.Doc showsPrec :: Int -> DocSection -> ShowS # show :: DocSection -> String # showList :: [DocSection] -> ShowS # |
type DocBlock = Map DocItemPos DocSection Source #
A map from positions to document elements.
This form effeciently keeps documentation for its incremental building.
Doc items here appear close to how they were located in the contract;
for instance, docItemsOrder
is not yet applied at this stage.
You only can be sure that items within each group are splitted across
sections correctly.
A part of documentation to be grouped. Essentially incapsulates DocBlock
.
Instances
Show DocGrouping Source # | |
Defined in Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # |
data ContractDoc Source #
Keeps documentation gathered for some piece of contract code.
Used for building documentation of a contract.
ContractDoc | |
|
Instances
Semigroup ContractDoc Source # | Contract documentation assembly primarily relies on this instance. |
Defined in Michelson.Doc (<>) :: ContractDoc -> ContractDoc -> ContractDoc # sconcat :: NonEmpty ContractDoc -> ContractDoc # stimes :: Integral b => b -> ContractDoc -> ContractDoc # | |
Monoid ContractDoc Source # | |
Defined in Michelson.Doc mempty :: ContractDoc # mappend :: ContractDoc -> ContractDoc -> ContractDoc # mconcat :: [ContractDoc] -> ContractDoc # |
type DocGrouping = SubDoc -> SomeDocItem Source #
A function which groups a piece of doc under one doc item.
deIsAtomic :: DocElem d -> Bool Source #
subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown Source #
Render documentation for SubDoc
.
docItemToBlock :: forall di. DocItem di => di -> DocBlock Source #
Lift an atomic doc item to a block.
lookupDocBlockSection :: forall d. DocItem d => DocBlock -> Maybe (NonEmpty d) Source #
Find all doc items of the given type.
contractDocToMarkdown :: ContractDoc -> LText Source #
Render given contract documentation to markdown document.
docGroupContent :: DocGrouping -> ContractDoc -> ContractDoc Source #
Apply given grouping to documentation being built.
docDefinitionRef :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => Markdown -> d -> Markdown Source #
Make a reference to doc item in definitions.
mdTocFromRef :: (DocItem d, DocItemReferenced d ~ 'True) => HeaderLevel -> Markdown -> d -> Markdown Source #
Generate DToc
entry anchor from docItemRef
.
newtype DGeneralInfoSection Source #
General (meta-)information about the contract such as git revision, contract's authors, etc. Should be relatively short (not several pages) because it is put somewhere close to the beginning of documentation.
Instances
Give a name to document block.
Instances
DocItem DName Source # | |
Defined in Michelson.Doc type DocItemPlacement DName :: DocItemPlacementKind Source # type DocItemReferenced DName :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DName -> DocItemRef (DocItemPlacement DName) (DocItemReferenced DName) Source # docItemToMarkdown :: HeaderLevel -> DName -> Markdown Source # docItemToToc :: HeaderLevel -> DName -> Markdown Source # docItemDependencies :: DName -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DName] -> [DName] Source # | |
type DocItemPlacement DName Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DName Source # | |
Defined in Michelson.Doc |
data DDescription Source #
Description of something.
Instances
DocItem DDescription Source # | |
Defined in Michelson.Doc type DocItemPlacement DDescription :: DocItemPlacementKind Source # type DocItemReferenced DDescription :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DDescription -> DocItemRef (DocItemPlacement DDescription) (DocItemReferenced DDescription) Source # docItemToMarkdown :: HeaderLevel -> DDescription -> Markdown Source # docItemToToc :: HeaderLevel -> DDescription -> Markdown Source # docItemDependencies :: DDescription -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DDescription] -> [DDescription] Source # | |
type DocItemPlacement DDescription Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DDescription Source # | |
Defined in Michelson.Doc |
data DGitRevision Source #
DGitRevisionKnown DGitRevisionInfo | |
DGitRevisionUnknown |
Instances
DocItem DGitRevision Source # | |
Defined in Michelson.Doc type DocItemPlacement DGitRevision :: DocItemPlacementKind Source # type DocItemReferenced DGitRevision :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DGitRevision -> DocItemRef (DocItemPlacement DGitRevision) (DocItemReferenced DGitRevision) Source # docItemToMarkdown :: HeaderLevel -> DGitRevision -> Markdown Source # docItemToToc :: HeaderLevel -> DGitRevision -> Markdown Source # docItemDependencies :: DGitRevision -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DGitRevision] -> [DGitRevision] Source # | |
type DocItemPlacement DGitRevision Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DGitRevision Source # | |
Defined in Michelson.Doc |
newtype GitRepoSettings Source #
Repository settings for DGitRevision
.
GitRepoSettings | |
|
mkDGitRevision :: ExpQ Source #
Make DGitRevision
.
>>>
:t $mkDGitRevision
GitRepoSettings -> DGitRevision
Comment in the doc (mostly used for licenses)
Instances
DocItem DComment Source # | |
Defined in Michelson.Doc type DocItemPlacement DComment :: DocItemPlacementKind Source # type DocItemReferenced DComment :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DComment -> DocItemRef (DocItemPlacement DComment) (DocItemReferenced DComment) Source # docItemToMarkdown :: HeaderLevel -> DComment -> Markdown Source # docItemToToc :: HeaderLevel -> DComment -> Markdown Source # docItemDependencies :: DComment -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DComment] -> [DComment] Source # | |
type DocItemPlacement DComment Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DComment Source # | |
Defined in Michelson.Doc |
A hand-made anchor.
Instances
DocItem DAnchor Source # | |
Defined in Michelson.Doc type DocItemPlacement DAnchor :: DocItemPlacementKind Source # type DocItemReferenced DAnchor :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DAnchor -> DocItemRef (DocItemPlacement DAnchor) (DocItemReferenced DAnchor) Source # docItemToMarkdown :: HeaderLevel -> DAnchor -> Markdown Source # docItemToToc :: HeaderLevel -> DAnchor -> Markdown Source # docItemDependencies :: DAnchor -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DAnchor] -> [DAnchor] Source # | |
type DocItemPlacement DAnchor Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DAnchor Source # | |
Defined in Michelson.Doc |
Table of contents
to be inserted into the doc in an ad-hoc way.
It is not intended to be inserted manually. See attachToc
to understand
how this works.
Instances
DocItem DToc Source # | |
Defined in Michelson.Doc type DocItemPlacement DToc :: DocItemPlacementKind Source # type DocItemReferenced DToc :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DToc -> DocItemRef (DocItemPlacement DToc) (DocItemReferenced DToc) Source # docItemToMarkdown :: HeaderLevel -> DToc -> Markdown Source # docItemToToc :: HeaderLevel -> DToc -> Markdown Source # docItemDependencies :: DToc -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DToc] -> [DToc] Source # | |
type DocItemPlacement DToc Source # | |
Defined in Michelson.Doc | |
type DocItemReferenced DToc Source # | |
Defined in Michelson.Doc |