Safe Haskell | None |
---|---|
Language | Haskell2010 |
Lorentz.Doc
Contents
Synopsis
- doc :: DocItem di => di -> s :-> s
- docGroup :: DocItem di => (SubDoc -> di) -> (inp :-> out) -> inp :-> out
- dStorage :: TypeHasDoc store => DStorageType
- docStorage :: forall storage s. TypeHasDoc storage => s :-> s
- buildLorentzDoc :: (inp :-> out) -> ContractDoc
- buildLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> ContractDoc
- renderLorentzDoc :: (inp :-> out) -> LText
- renderLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> LText
- contractName :: Text -> (inp :-> out) -> inp :-> out
- contractGeneral :: (inp :-> out) -> inp :-> out
- contractGeneralDefault :: s :-> s
- cutLorentzNonDoc :: (inp :-> out) -> s :-> s
- type Markdown = Builder
- data DocElem d = DocElem {}
- 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 :: DocItem d => DocItemPos
- newtype DocItemId = DocItemId Text
- data DocItemPlacementKind
- newtype DocItemPos = DocItemPos (Natural, Text)
- data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where
- data DocSection = DocItem d => DocSection (NonEmpty $ DocElem d)
- data DocSectionNameStyle
- data SomeDocItem where
- SomeDocItem :: forall d. DocItem d => d -> SomeDocItem
- data SomeDocDefinitionItem where
- SomeDocDefinitionItem :: forall d. (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem
- newtype SubDoc = SubDoc DocBlock
- type DocGrouping = SubDoc -> SomeDocItem
- data ContractDoc = ContractDoc {
- cdContents :: DocBlock
- cdDefinitions :: DocBlock
- cdDefinitionsSet :: Set SomeDocDefinitionItem
- cdDefinitionIds :: Set DocItemId
- newtype DGeneralInfoSection = DGeneralInfoSection SubDoc
- data DName = DName Text SubDoc
- data DDescription = DDescription Markdown
- data DEntrypointExample = forall t.ParameterScope t => DEntrypointExample (Value t)
- mkDEntrypointExample :: forall a. NiceParameter a => a -> DEntrypointExample
- data DGitRevision
- = DGitRevisionKnown DGitRevisionInfo
- | DGitRevisionUnknown
- newtype GitRepoSettings = GitRepoSettings {
- grsMkGitRevision :: Text -> Text
- mkDGitRevision :: ExpQ
- morleyRepoSettings :: GitRepoSettings
- data DComment = DComment Text
- data DAnchor = DAnchor Anchor
- data DType where
- DType :: forall a. TypeHasDoc a => Proxy a -> DType
- dTypeDep :: TypeHasDoc t => SomeDocDefinitionItem
- docDefinitionRef :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => Markdown -> d -> Markdown
- contractDocToMarkdown :: ContractDoc -> LText
- subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown
- docItemSectionRef :: DocItem di => Maybe Markdown
- class ContainsDoc a where
- buildDocUnfinalized :: a -> ContractDoc
- class ContainsDoc a => ContainsUpdateableDoc a where
- modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> a -> a
- data WithFinalizedDoc a
- finalizedAsIs :: a -> WithFinalizedDoc a
- buildDoc :: ContainsDoc a => WithFinalizedDoc a -> ContractDoc
- buildMarkdownDoc :: ContainsDoc a => WithFinalizedDoc a -> LText
- modifyDoc :: (ContainsUpdateableDoc a, DocItem i1, DocItem i2) => (i1 -> Maybe i2) -> a -> a
- attachDocCommons :: ContainsUpdateableDoc a => DGitRevision -> a -> WithFinalizedDoc a
- class (Typeable a, SingI (TypeDocFieldDescriptions a), FieldDescriptionsValid (TypeDocFieldDescriptions a) a) => TypeHasDoc a where
- type TypeDocFieldDescriptions a :: FieldDescriptions
- typeDocName :: Proxy a -> Text
- typeDocMdDescription :: Markdown
- typeDocMdReference :: Proxy a -> WithinParens -> Markdown
- typeDocDependencies :: Proxy a -> [SomeDocDefinitionItem]
- typeDocHaskellRep :: TypeDocHaskellRep a
- typeDocMichelsonRep :: TypeDocMichelsonRep a
- data SomeTypeWithDoc where
- SomeTypeWithDoc :: forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc
- class HaveCommonTypeCtor (a :: k) (b :: k1)
- class IsHomomorphic (a :: k)
- genericTypeDocDependencies :: (Generic a, GTypeHasDoc (Rep a)) => Proxy a -> [SomeDocDefinitionItem]
- customTypeDocMdReference :: (Text, DType) -> [DType] -> WithinParens -> Markdown
- homomorphicTypeDocMdReference :: (Typeable t, TypeHasDoc t, IsHomomorphic t) => Proxy t -> WithinParens -> Markdown
- poly1TypeDocMdReference :: forall (t :: Type -> Type) r a. (r ~ t a, Typeable t, Each '[TypeHasDoc] '[r, a], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown
- 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
- homomorphicTypeDocHaskellRep :: (Generic a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep a
- concreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b
- concreteTypeDocHaskellRepUnsafe :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep b
- haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepStripFieldPrefix :: HasCallStack => TypeDocHaskellRep a -> TypeDocHaskellRep a
- homomorphicTypeDocMichelsonRep :: SingI (ToT a) => TypeDocMichelsonRep a
- concreteTypeDocMichelsonRep :: forall k a (b :: k). (Typeable a, SingI (ToT a), HaveCommonTypeCtor b a) => TypeDocMichelsonRep b
- concreteTypeDocMichelsonRepUnsafe :: forall k a (b :: k). (Typeable a, SingI (ToT a)) => TypeDocMichelsonRep b
- mdTocFromRef :: (DocItem d, DocItemReferenced d ~ 'True) => HeaderLevel -> Markdown -> d -> Markdown
Documentation
docGroup :: DocItem di => (SubDoc -> di) -> (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.
Examples of doc items you can pass here: DName
, DGeneralInfoSection
.
dStorage :: TypeHasDoc store => DStorageType #
docStorage :: forall storage s. TypeHasDoc storage => s :-> s Source #
Deprecated: Use `doc (dStorage @storage)` instead.
Insert documentation of the contract storage type. The type should be passed using type applications.
buildLorentzDoc :: (inp :-> out) -> ContractDoc Source #
Deprecated: Use buildDoc
instead.
buildLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> ContractDoc Source #
Deprecated: Use `buildDoc . attachDocCommons gitRev` instead.
renderLorentzDoc :: (inp :-> out) -> LText Source #
Deprecated: Use buildMarkdownDoc
instead.
renderLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> LText Source #
Deprecated: Use `buildMarkdownDoc . attachDocCommons gitRev` instead.
contractName :: Text -> (inp :-> out) -> inp :-> out Source #
Deprecated: Use `docGroup name` instead.
Give a name to given contract. Apply it to the whole contract code.
contractGeneral :: (inp :-> out) -> inp :-> out Source #
Deprecated: Use `docGroup DGeneralInfoSection` instead.
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.
This includes git revision and some other information common
for all contracts.
Git revision is left unknown in the library code and is supposed
to be updated in an executable using e.g. buildLorentzDocWithGitRev
.
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
class (Typeable d, DOrd d) => DocItem d where #
Minimal complete definition
Associated Types
type DocItemPlacement d :: DocItemPlacementKind #
type DocItemPlacement d = 'DocItemInlined
type DocItemReferenced d :: DocItemReferencedKind #
type DocItemReferenced d = 'False
Methods
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] #
Instances
docItemPosition :: DocItem d => DocItemPos #
Instances
Eq DocItemId | |
Ord DocItemId | |
Show DocItemId | |
ToAnchor DocItemId | |
Defined in Michelson.Doc |
data DocItemPlacementKind #
Constructors
DocItemInlined | |
DocItemInDefinitions |
newtype DocItemPos #
Constructors
DocItemPos (Natural, Text) |
Instances
Eq DocItemPos | |
Defined in Michelson.Doc | |
Ord DocItemPos | |
Defined in Michelson.Doc Methods 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 | |
Defined in Michelson.Doc Methods showsPrec :: Int -> DocItemPos -> ShowS # show :: DocItemPos -> String # showList :: [DocItemPos] -> ShowS # | |
Buildable DocItemPos | |
Defined in Michelson.Doc Methods build :: DocItemPos -> Builder # |
data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where #
Constructors
DocItemRef :: DocItemId -> DocItemRef 'DocItemInDefinitions 'True | |
DocItemRefInlined :: DocItemId -> DocItemRef 'DocItemInlined 'True | |
DocItemNoRef :: DocItemRef 'DocItemInlined 'False |
Instances
ToAnchor (DocItemRef d 'True) | |
Defined in Michelson.Doc Methods toAnchor :: DocItemRef d 'True -> Anchor |
data DocSection #
Constructors
DocItem d => DocSection (NonEmpty $ DocElem d) |
Instances
Show DocSection | |
Defined in Michelson.Doc Methods showsPrec :: Int -> DocSection -> ShowS # show :: DocSection -> String # showList :: [DocSection] -> ShowS # |
data DocSectionNameStyle #
Constructors
DocSectionNameBig | |
DocSectionNameSmall |
data SomeDocItem where #
Constructors
SomeDocItem :: forall d. DocItem d => d -> SomeDocItem |
Instances
Show SomeDocItem | |
Defined in Michelson.Doc Methods showsPrec :: Int -> SomeDocItem -> ShowS # show :: SomeDocItem -> String # showList :: [SomeDocItem] -> ShowS # | |
Show DocGrouping | |
Defined in Michelson.Doc Methods showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
NFData SomeDocItem | |
Defined in Michelson.Doc Methods rnf :: SomeDocItem -> () # |
data SomeDocDefinitionItem where #
Constructors
SomeDocDefinitionItem :: forall d. (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem |
Instances
Eq SomeDocDefinitionItem | |
Defined in Michelson.Doc Methods (==) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (/=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # | |
Ord SomeDocDefinitionItem | |
Defined in Michelson.Doc Methods compare :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Ordering # (<) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (<=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (>) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (>=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # max :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> SomeDocDefinitionItem # min :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> SomeDocDefinitionItem # |
Constructors
SubDoc DocBlock |
Instances
Show DocGrouping | |
Defined in Michelson.Doc Methods showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
di ~ DName => IsString (SubDoc -> di) | |
Defined in Michelson.Doc Methods fromString :: String -> SubDoc -> di # |
type DocGrouping = SubDoc -> SomeDocItem #
data ContractDoc #
Constructors
ContractDoc | |
Fields
|
Instances
Semigroup ContractDoc | |
Defined in Michelson.Doc Methods (<>) :: ContractDoc -> ContractDoc -> ContractDoc # sconcat :: NonEmpty ContractDoc -> ContractDoc # stimes :: Integral b => b -> ContractDoc -> ContractDoc # | |
Monoid ContractDoc | |
Defined in Michelson.Doc Methods mempty :: ContractDoc # mappend :: ContractDoc -> ContractDoc -> ContractDoc # mconcat :: [ContractDoc] -> ContractDoc # |
newtype DGeneralInfoSection #
Constructors
DGeneralInfoSection SubDoc |
Instances
DocItem DGeneralInfoSection | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DGeneralInfoSection :: DocItemPlacementKind # type DocItemReferenced DGeneralInfoSection :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DGeneralInfoSection -> DocItemRef (DocItemPlacement DGeneralInfoSection) (DocItemReferenced DGeneralInfoSection) # docItemToMarkdown :: HeaderLevel -> DGeneralInfoSection -> Markdown # docItemToToc :: HeaderLevel -> DGeneralInfoSection -> Markdown # docItemDependencies :: DGeneralInfoSection -> [SomeDocDefinitionItem] # docItemsOrder :: [DGeneralInfoSection] -> [DGeneralInfoSection] # | |
type DocItemPlacement DGeneralInfoSection | |
Defined in Michelson.Doc | |
type DocItemReferenced DGeneralInfoSection | |
Defined in Michelson.Doc |
Instances
DocItem DName | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DName :: DocItemPlacementKind # type DocItemReferenced DName :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DName -> DocItemRef (DocItemPlacement DName) (DocItemReferenced DName) # docItemToMarkdown :: HeaderLevel -> DName -> Markdown # docItemToToc :: HeaderLevel -> DName -> Markdown # docItemDependencies :: DName -> [SomeDocDefinitionItem] # docItemsOrder :: [DName] -> [DName] # | |
type DocItemPlacement DName | |
Defined in Michelson.Doc | |
type DocItemReferenced DName | |
Defined in Michelson.Doc |
data DDescription #
Constructors
DDescription Markdown |
Instances
DocItem DDescription | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DDescription :: DocItemPlacementKind # type DocItemReferenced DDescription :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DDescription -> DocItemRef (DocItemPlacement DDescription) (DocItemReferenced DDescription) # docItemToMarkdown :: HeaderLevel -> DDescription -> Markdown # docItemToToc :: HeaderLevel -> DDescription -> Markdown # docItemDependencies :: DDescription -> [SomeDocDefinitionItem] # docItemsOrder :: [DDescription] -> [DDescription] # | |
type DocItemPlacement DDescription | |
Defined in Michelson.Doc | |
type DocItemReferenced DDescription | |
Defined in Michelson.Doc |
data DEntrypointExample Source #
Modify the example value of an entrypoint
Constructors
forall t.ParameterScope t => DEntrypointExample (Value t) |
Instances
DocItem DEntrypointExample Source # | |
Defined in Lorentz.Doc Associated Types type DocItemPlacement DEntrypointExample :: DocItemPlacementKind # type DocItemReferenced DEntrypointExample :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DEntrypointExample -> DocItemRef (DocItemPlacement DEntrypointExample) (DocItemReferenced DEntrypointExample) # docItemToMarkdown :: HeaderLevel -> DEntrypointExample -> Markdown # docItemToToc :: HeaderLevel -> DEntrypointExample -> Markdown # docItemDependencies :: DEntrypointExample -> [SomeDocDefinitionItem] # docItemsOrder :: [DEntrypointExample] -> [DEntrypointExample] # | |
type DocItemPlacement DEntrypointExample Source # | |
Defined in Lorentz.Doc | |
type DocItemReferenced DEntrypointExample Source # | |
Defined in Lorentz.Doc |
mkDEntrypointExample :: forall a. NiceParameter a => a -> DEntrypointExample Source #
data DGitRevision #
Constructors
DGitRevisionKnown DGitRevisionInfo | |
DGitRevisionUnknown |
Instances
DocItem DGitRevision | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DGitRevision :: DocItemPlacementKind # type DocItemReferenced DGitRevision :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DGitRevision -> DocItemRef (DocItemPlacement DGitRevision) (DocItemReferenced DGitRevision) # docItemToMarkdown :: HeaderLevel -> DGitRevision -> Markdown # docItemToToc :: HeaderLevel -> DGitRevision -> Markdown # docItemDependencies :: DGitRevision -> [SomeDocDefinitionItem] # docItemsOrder :: [DGitRevision] -> [DGitRevision] # | |
type DocItemPlacement DGitRevision | |
Defined in Michelson.Doc | |
type DocItemReferenced DGitRevision | |
Defined in Michelson.Doc |
newtype GitRepoSettings #
Constructors
GitRepoSettings | |
Fields
|
mkDGitRevision :: ExpQ #
Instances
DocItem DComment | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DComment :: DocItemPlacementKind # type DocItemReferenced DComment :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DComment -> DocItemRef (DocItemPlacement DComment) (DocItemReferenced DComment) # docItemToMarkdown :: HeaderLevel -> DComment -> Markdown # docItemToToc :: HeaderLevel -> DComment -> Markdown # docItemDependencies :: DComment -> [SomeDocDefinitionItem] # docItemsOrder :: [DComment] -> [DComment] # | |
type DocItemPlacement DComment | |
Defined in Michelson.Doc | |
type DocItemReferenced DComment | |
Defined in Michelson.Doc |
Constructors
DAnchor Anchor |
Instances
DocItem DAnchor | |
Defined in Michelson.Doc Associated Types type DocItemPlacement DAnchor :: DocItemPlacementKind # type DocItemReferenced DAnchor :: DocItemReferencedKind # Methods docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DAnchor -> DocItemRef (DocItemPlacement DAnchor) (DocItemReferenced DAnchor) # docItemToMarkdown :: HeaderLevel -> DAnchor -> Markdown # docItemToToc :: HeaderLevel -> DAnchor -> Markdown # docItemDependencies :: DAnchor -> [SomeDocDefinitionItem] # docItemsOrder :: [DAnchor] -> [DAnchor] # | |
type DocItemPlacement DAnchor | |
Defined in Michelson.Doc | |
type DocItemReferenced DAnchor | |
Defined in Michelson.Doc |
Constructors
DType :: forall a. TypeHasDoc a => Proxy a -> DType |
Instances
Eq DType | |
Ord DType | |
Show DType | |
DocItem DType | |
Defined in 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] # | |
type DocItemPlacement DType | |
Defined in Michelson.Typed.Haskell.Doc | |
type DocItemReferenced DType | |
Defined in Michelson.Typed.Haskell.Doc |
dTypeDep :: TypeHasDoc t => SomeDocDefinitionItem #
docDefinitionRef :: (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => Markdown -> d -> Markdown #
subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown #
docItemSectionRef :: DocItem di => Maybe Markdown #
class ContainsDoc a where #
Methods
buildDocUnfinalized :: a -> ContractDoc #
Instances
ContainsDoc (i :-> o) Source # | |
Defined in Lorentz.Doc Methods buildDocUnfinalized :: (i :-> o) -> ContractDoc # | |
ContainsDoc (Contract cp st) Source # | |
Defined in Lorentz.Run Methods buildDocUnfinalized :: Contract cp st -> ContractDoc # |
class ContainsDoc a => ContainsUpdateableDoc a where #
Methods
modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> a -> a #
Instances
ContainsUpdateableDoc (i :-> o) Source # | |
Defined in Lorentz.Doc Methods modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o # | |
ContainsUpdateableDoc (Contract cp st) Source # | |
Defined in Lorentz.Run Methods modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st -> Contract cp st # |
data WithFinalizedDoc a #
Instances
Monad WithFinalizedDoc | |
Defined in Michelson.Doc Methods (>>=) :: WithFinalizedDoc a -> (a -> WithFinalizedDoc b) -> WithFinalizedDoc b # (>>) :: WithFinalizedDoc a -> WithFinalizedDoc b -> WithFinalizedDoc b # return :: a -> WithFinalizedDoc a # | |
Functor WithFinalizedDoc | |
Defined in Michelson.Doc Methods fmap :: (a -> b) -> WithFinalizedDoc a -> WithFinalizedDoc b # (<$) :: a -> WithFinalizedDoc b -> WithFinalizedDoc a # | |
Applicative WithFinalizedDoc | |
Defined in Michelson.Doc Methods pure :: a -> WithFinalizedDoc a # (<*>) :: WithFinalizedDoc (a -> b) -> WithFinalizedDoc a -> WithFinalizedDoc b # liftA2 :: (a -> b -> c) -> WithFinalizedDoc a -> WithFinalizedDoc b -> WithFinalizedDoc c # (*>) :: WithFinalizedDoc a -> WithFinalizedDoc b -> WithFinalizedDoc b # (<*) :: WithFinalizedDoc a -> WithFinalizedDoc b -> WithFinalizedDoc a # |
finalizedAsIs :: a -> WithFinalizedDoc a #
buildDoc :: ContainsDoc a => WithFinalizedDoc a -> ContractDoc #
buildMarkdownDoc :: ContainsDoc a => WithFinalizedDoc a -> LText #
attachDocCommons :: ContainsUpdateableDoc a => DGitRevision -> a -> WithFinalizedDoc a #
class (Typeable a, SingI (TypeDocFieldDescriptions a), FieldDescriptionsValid (TypeDocFieldDescriptions a) a) => TypeHasDoc a where #
Minimal complete definition
Associated Types
type TypeDocFieldDescriptions a :: FieldDescriptions #
Methods
typeDocName :: Proxy a -> Text #
typeDocMdDescription :: Markdown #
typeDocMdReference :: Proxy a -> WithinParens -> Markdown #
typeDocDependencies :: Proxy a -> [SomeDocDefinitionItem] #
typeDocHaskellRep :: TypeDocHaskellRep a #
typeDocMichelsonRep :: TypeDocMichelsonRep a #
Instances
data SomeTypeWithDoc where #
Constructors
SomeTypeWithDoc :: forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc |
class HaveCommonTypeCtor (a :: k) (b :: k1) #
Instances
HaveCommonTypeCtor (a :: k) (a :: k) | |
Defined in Michelson.Typed.Haskell.Doc | |
HaveCommonTypeCtor ac bc => HaveCommonTypeCtor (ac a :: k2) (bc b :: k4) | |
Defined in Michelson.Typed.Haskell.Doc |
class IsHomomorphic (a :: k) #
Instances
IsHomomorphic (a :: k) | |
Defined in Michelson.Typed.Haskell.Doc | |
(TypeError ('Text "Type is not homomorphic: " :<>: 'ShowType (a b)) :: Constraint) => IsHomomorphic (a b :: k2) | |
Defined in Michelson.Typed.Haskell.Doc |
genericTypeDocDependencies :: (Generic a, GTypeHasDoc (Rep a)) => Proxy a -> [SomeDocDefinitionItem] #
homomorphicTypeDocMdReference :: (Typeable t, TypeHasDoc t, IsHomomorphic t) => Proxy t -> WithinParens -> Markdown #
poly1TypeDocMdReference :: forall (t :: Type -> Type) r a. (r ~ t a, Typeable t, Each '[TypeHasDoc] '[r, a], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown #
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 #
homomorphicTypeDocHaskellRep :: (Generic a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep a #
concreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b #
concreteTypeDocHaskellRepUnsafe :: (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep b #
haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a #
haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a #
haskellRepStripFieldPrefix :: HasCallStack => TypeDocHaskellRep a -> TypeDocHaskellRep a #
homomorphicTypeDocMichelsonRep :: SingI (ToT a) => TypeDocMichelsonRep a #
concreteTypeDocMichelsonRep :: forall k a (b :: k). (Typeable a, SingI (ToT a), HaveCommonTypeCtor b a) => TypeDocMichelsonRep b #
concreteTypeDocMichelsonRepUnsafe :: forall k a (b :: k). (Typeable a, SingI (ToT a)) => TypeDocMichelsonRep b #
mdTocFromRef :: (DocItem d, DocItemReferenced d ~ 'True) => HeaderLevel -> Markdown -> d -> Markdown #