Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- doc :: DocItem di => di -> s :-> s
- docGroup :: DocItem di => (SubDoc -> di) -> (inp :-> out) -> inp :-> out
- dStorage :: TypeHasDoc store => DStorageType
- contractGeneralDefault :: s :-> s
- cutLorentzNonDoc :: (inp :-> out) -> s :-> s
- data DView = DView {}
- data DViewArg = forall a.(NiceViewable a, TypeHasDoc a) => DViewArg (Proxy a)
- data DViewRet = forall a.(NiceViewable a, TypeHasDoc a) => DViewRet (Proxy a)
- data DViewDesc = forall vd.ViewsDescriptorHasDoc vd => DViewDesc (Proxy vd)
- class (Typeable vd, RenderViewsImpl (RevealViews vd)) => ViewsDescriptorHasDoc (vd :: Type) where
- viewsDescriptorName :: Proxy vd -> Text
- renderViewsDescriptorDoc :: Proxy vd -> Doc
- type Markdown = Doc
- 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
- class TypeHasFieldNamingStrategy (a :: k) where
- typeFieldNamingStrategy :: Text -> Text
- data SomeTypeWithDoc where
- SomeTypeWithDoc :: forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc
- typeDocBuiltMichelsonRep :: TypeHasDoc a => Proxy a -> Doc
- type family HaveCommonTypeCtor (a :: k) (b :: k) where ...
- class IsHomomorphic (a :: k)
- genericTypeDocDependencies :: (Generic a, GTypeHasDoc (GRep 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 (GRep a)) => TypeDocHaskellRep a
- concreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b
- unsafeConcreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep b
- haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a
- homomorphicTypeDocMichelsonRep :: KnownIsoT a => TypeDocMichelsonRep a
- concreteTypeDocMichelsonRep :: (Typeable a, KnownIsoT a, HaveCommonTypeCtor b a) => TypeDocMichelsonRep b
- unsafeConcreteTypeDocMichelsonRep :: forall {k} a (b :: k). (Typeable a, KnownIsoT 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 #
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. attachDocCommons
.
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.
Views
Renders to a view section.
Instances
DocItem DView Source # | |
Defined in Lorentz.Doc type DocItemPlacement DView :: DocItemPlacementKind # type DocItemReferenced DView :: DocItemReferencedKind # docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DView -> DocItemRef (DocItemPlacement DView) (DocItemReferenced DView) # docItemToMarkdown :: HeaderLevel -> DView -> Markdown # docItemToToc :: HeaderLevel -> DView -> Markdown # docItemDependencies :: DView -> [SomeDocDefinitionItem] # docItemsOrder :: [DView] -> [DView] # | |
type DocItemPlacement DView Source # | |
Defined in Lorentz.Doc | |
type DocItemReferenced DView Source # | |
Defined in Lorentz.Doc |
Renders to a line mentioning the view's argument.
forall a.(NiceViewable a, TypeHasDoc a) => DViewArg (Proxy a) |
Instances
DocItem DViewArg Source # | |
Defined in Lorentz.Doc type DocItemPlacement DViewArg :: DocItemPlacementKind # type DocItemReferenced DViewArg :: DocItemReferencedKind # docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DViewArg -> DocItemRef (DocItemPlacement DViewArg) (DocItemReferenced DViewArg) # docItemToMarkdown :: HeaderLevel -> DViewArg -> Markdown # docItemToToc :: HeaderLevel -> DViewArg -> Markdown # docItemDependencies :: DViewArg -> [SomeDocDefinitionItem] # docItemsOrder :: [DViewArg] -> [DViewArg] # | |
type DocItemPlacement DViewArg Source # | |
Defined in Lorentz.Doc | |
type DocItemReferenced DViewArg Source # | |
Defined in Lorentz.Doc |
Renders to a line mentioning the view's argument.
forall a.(NiceViewable a, TypeHasDoc a) => DViewRet (Proxy a) |
Instances
DocItem DViewRet Source # | |
Defined in Lorentz.Doc type DocItemPlacement DViewRet :: DocItemPlacementKind # type DocItemReferenced DViewRet :: DocItemReferencedKind # docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DViewRet -> DocItemRef (DocItemPlacement DViewRet) (DocItemReferenced DViewRet) # docItemToMarkdown :: HeaderLevel -> DViewRet -> Markdown # docItemToToc :: HeaderLevel -> DViewRet -> Markdown # docItemDependencies :: DViewRet -> [SomeDocDefinitionItem] # docItemsOrder :: [DViewRet] -> [DViewRet] # | |
type DocItemPlacement DViewRet Source # | |
Defined in Lorentz.Doc | |
type DocItemReferenced DViewRet Source # | |
Defined in Lorentz.Doc |
Renders to documentation of view descriptor.
forall vd.ViewsDescriptorHasDoc vd => DViewDesc (Proxy vd) |
Instances
Eq DViewDesc Source # | |
Ord DViewDesc Source # | |
Defined in Lorentz.Doc | |
DocItem DViewDesc Source # | |
Defined in Lorentz.Doc type DocItemPlacement DViewDesc :: DocItemPlacementKind # type DocItemReferenced DViewDesc :: DocItemReferencedKind # docItemPos :: Natural # docItemSectionName :: Maybe Text # docItemSectionDescription :: Maybe Markdown # docItemSectionNameStyle :: DocSectionNameStyle # docItemRef :: DViewDesc -> DocItemRef (DocItemPlacement DViewDesc) (DocItemReferenced DViewDesc) # docItemToMarkdown :: HeaderLevel -> DViewDesc -> Markdown # docItemToToc :: HeaderLevel -> DViewDesc -> Markdown # docItemDependencies :: DViewDesc -> [SomeDocDefinitionItem] # docItemsOrder :: [DViewDesc] -> [DViewDesc] # | |
type DocItemPlacement DViewDesc Source # | |
Defined in Lorentz.Doc | |
type DocItemReferenced DViewDesc Source # | |
Defined in Lorentz.Doc |
class (Typeable vd, RenderViewsImpl (RevealViews vd)) => ViewsDescriptorHasDoc (vd :: Type) where Source #
Provides documentation for views descriptor.
Note that views descriptors may describe views that do not belong to the
current contract, e.g. TAddress
may refer to an external contract provided
by the user in which we want to call a view.
Nothing
viewsDescriptorName :: Proxy vd -> Text Source #
default viewsDescriptorName :: (Generic vd, KnownSymbol (GenericTypeName vd)) => Proxy vd -> Text Source #
renderViewsDescriptorDoc :: Proxy vd -> Doc Source #
Re-exports
class (Typeable d, DOrd d) => DocItem d where #
type DocItemPlacement d :: DocItemPlacementKind #
type DocItemPlacement d = 'DocItemInlined
type DocItemReferenced d :: DocItemReferencedKind #
type DocItemReferenced d = 'False
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
Show DocItemId | |
Eq DocItemId | |
Ord DocItemId | |
Defined in Morley.Michelson.Doc | |
ToAnchor DocItemId | |
Defined in Morley.Michelson.Doc |
newtype DocItemPos #
Instances
Show DocItemPos | |
Defined in Morley.Michelson.Doc showsPrec :: Int -> DocItemPos -> ShowS # show :: DocItemPos -> String # showList :: [DocItemPos] -> ShowS # | |
Eq DocItemPos | |
Defined in Morley.Michelson.Doc (==) :: DocItemPos -> DocItemPos -> Bool # (/=) :: DocItemPos -> DocItemPos -> Bool # | |
Ord DocItemPos | |
Defined in Morley.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 # | |
Buildable DocItemPos | |
Defined in Morley.Michelson.Doc build :: DocItemPos -> Doc buildList :: [DocItemPos] -> Doc |
data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where #
DocItemRef :: DocItemId -> DocItemRef 'DocItemInDefinitions 'True | |
DocItemRefInlined :: DocItemId -> DocItemRef 'DocItemInlined 'True | |
DocItemNoRef :: DocItemRef 'DocItemInlined 'False |
Instances
ToAnchor (DocItemRef d 'True) | |
Defined in Morley.Michelson.Doc toAnchor :: DocItemRef d 'True -> Anchor |
data DocSection #
DocItem d => DocSection (NonEmpty $ DocElem d) |
data SomeDocItem where #
SomeDocItem :: forall d. DocItem d => d -> SomeDocItem |
Instances
Show DocGrouping | |
Defined in Morley.Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
Show SomeDocItem | |
Defined in Morley.Michelson.Doc showsPrec :: Int -> SomeDocItem -> ShowS # show :: SomeDocItem -> String # showList :: [SomeDocItem] -> ShowS # | |
NFData SomeDocItem | |
Defined in Morley.Michelson.Doc rnf :: SomeDocItem -> () # |
data SomeDocDefinitionItem where #
SomeDocDefinitionItem :: forall d. (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem |
Instances
Eq SomeDocDefinitionItem | |
Defined in Morley.Michelson.Doc (==) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (/=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # | |
Ord SomeDocDefinitionItem | |
Defined in Morley.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 # |
SubDoc DocBlock |
Instances
Show DocGrouping | |
Defined in Morley.Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
di ~ DName => IsString (SubDoc -> di) | |
Defined in Morley.Michelson.Doc fromString :: String -> SubDoc -> di # |
type DocGrouping = SubDoc -> SomeDocItem #
data ContractDoc #
ContractDoc | |
|
Instances
Monoid ContractDoc | |
Defined in Morley.Michelson.Doc mempty :: ContractDoc # mappend :: ContractDoc -> ContractDoc -> ContractDoc # mconcat :: [ContractDoc] -> ContractDoc # | |
Semigroup ContractDoc | |
Defined in Morley.Michelson.Doc (<>) :: ContractDoc -> ContractDoc -> ContractDoc # sconcat :: NonEmpty ContractDoc -> ContractDoc # stimes :: Integral b => b -> ContractDoc -> ContractDoc # |
newtype DGeneralInfoSection #
Instances
DocItem DGeneralInfoSection | |
Defined in Morley.Michelson.Doc type DocItemPlacement DGeneralInfoSection :: DocItemPlacementKind # type DocItemReferenced DGeneralInfoSection :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DGeneralInfoSection | |
Defined in Morley.Michelson.Doc |
Instances
DocItem DName | |
Defined in Morley.Michelson.Doc type DocItemPlacement DName :: DocItemPlacementKind # type DocItemReferenced DName :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DName | |
Defined in Morley.Michelson.Doc |
data DDescription #
Instances
DocItem DDescription | |
Defined in Morley.Michelson.Doc type DocItemPlacement DDescription :: DocItemPlacementKind # type DocItemReferenced DDescription :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DDescription | |
Defined in Morley.Michelson.Doc |
data DEntrypointExample Source #
Modify the example value of an entrypoint
forall t.ParameterScope t => DEntrypointExample (Value t) |
Instances
DocItem DEntrypointExample Source # | |
Defined in Lorentz.Doc type DocItemPlacement DEntrypointExample :: DocItemPlacementKind # type DocItemReferenced DEntrypointExample :: DocItemReferencedKind # 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 #
DGitRevisionKnown DGitRevisionInfo | |
DGitRevisionUnknown |
Instances
DocItem DGitRevision | |
Defined in Morley.Michelson.Doc type DocItemPlacement DGitRevision :: DocItemPlacementKind # type DocItemReferenced DGitRevision :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DGitRevision | |
Defined in Morley.Michelson.Doc |
newtype GitRepoSettings #
mkDGitRevision :: ExpQ #
Instances
DocItem DComment | |
Defined in Morley.Michelson.Doc type DocItemPlacement DComment :: DocItemPlacementKind # type DocItemReferenced DComment :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DComment | |
Defined in Morley.Michelson.Doc |
DAnchor Anchor |
Instances
DocItem DAnchor | |
Defined in Morley.Michelson.Doc type DocItemPlacement DAnchor :: DocItemPlacementKind # type DocItemReferenced DAnchor :: DocItemReferencedKind # 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 Morley.Michelson.Doc | |
type DocItemReferenced DAnchor | |
Defined in Morley.Michelson.Doc |
DType :: forall a. TypeHasDoc a => Proxy a -> DType |
Instances
Eq DType | |
Ord DType | |
DocItem DType | |
Defined in Morley.Michelson.Typed.Haskell.Doc type DocItemPlacement DType :: DocItemPlacementKind # type DocItemReferenced DType :: DocItemReferencedKind # 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 |
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 #
buildDocUnfinalized :: a -> ContractDoc #
Instances
ContainsDoc (i :-> o) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: (i :-> o) -> ContractDoc # | |
ContainsDoc (ContractCode i o) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: ContractCode i o -> ContractDoc # | |
ContainsDoc (Contract cp st vd) Source # | |
Defined in Lorentz.Doc buildDocUnfinalized :: Contract cp st vd -> ContractDoc # | |
ContainsDoc (ContractData cp st vd) Source # | |
Defined in Lorentz.Run buildDocUnfinalized :: ContractData cp st vd -> ContractDoc # |
class ContainsDoc a => ContainsUpdateableDoc a where #
modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> a -> a #
Instances
ContainsUpdateableDoc (i :-> o) Source # | |
Defined in Lorentz.Doc modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o # | |
ContainsUpdateableDoc (ContractCode i o) Source # | |
Defined in Lorentz.Doc modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> ContractCode i o -> ContractCode i o # | |
ContainsUpdateableDoc (Contract cp st vd) Source # | |
Defined in Lorentz.Doc modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st vd -> Contract cp st vd # | |
ContainsUpdateableDoc (ContractData cp st vd) Source # | |
Defined in Lorentz.Run modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> ContractData cp st vd -> ContractData cp st vd # |
data WithFinalizedDoc a #
Instances
Applicative WithFinalizedDoc | |
Defined in Morley.Michelson.Doc 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 # | |
Functor WithFinalizedDoc | |
Defined in Morley.Michelson.Doc fmap :: (a -> b) -> WithFinalizedDoc a -> WithFinalizedDoc b # (<$) :: a -> WithFinalizedDoc b -> WithFinalizedDoc a # | |
Monad WithFinalizedDoc | |
Defined in Morley.Michelson.Doc (>>=) :: WithFinalizedDoc a -> (a -> WithFinalizedDoc b) -> WithFinalizedDoc b # (>>) :: WithFinalizedDoc a -> WithFinalizedDoc b -> WithFinalizedDoc b # return :: a -> 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 #
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 #
Instances
class TypeHasFieldNamingStrategy (a :: k) where #
Nothing
typeFieldNamingStrategy :: Text -> Text #
Instances
TypeHasFieldNamingStrategy FieldCamelCase | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text # | |
TypeHasFieldNamingStrategy FieldSnakeCase | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text # | |
TypeHasFieldNamingStrategy (a :: k) | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text # | |
TypeHasFieldNamingStrategy (RangeFailureInfo a :: Type) Source # | |
Defined in Lorentz.Range typeFieldNamingStrategy :: Text -> Text # |
data SomeTypeWithDoc where #
SomeTypeWithDoc :: forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc |
typeDocBuiltMichelsonRep :: TypeHasDoc a => Proxy a -> Doc #
type family HaveCommonTypeCtor (a :: k) (b :: k) where ... #
HaveCommonTypeCtor (ac _1 :: k2) (bc _2 :: k2) = HaveCommonTypeCtor ac bc | |
HaveCommonTypeCtor (a :: k) (a :: k) = () |
class IsHomomorphic (a :: k) #
Instances
IsHomomorphic (a :: k) | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
(TypeError ('Text "Type is not homomorphic: " ':<>: 'ShowType (a b)) :: Constraint) => IsHomomorphic (a b :: k2) | |
Defined in Morley.Michelson.Typed.Haskell.Doc |
genericTypeDocDependencies :: (Generic a, GTypeHasDoc (GRep 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 (GRep a)) => TypeDocHaskellRep a #
concreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b #
unsafeConcreteTypeDocHaskellRep :: (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep b #
haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a #
haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a #
homomorphicTypeDocMichelsonRep :: KnownIsoT a => TypeDocMichelsonRep a #
concreteTypeDocMichelsonRep :: (Typeable a, KnownIsoT a, HaveCommonTypeCtor b a) => TypeDocMichelsonRep b #
unsafeConcreteTypeDocMichelsonRep :: forall {k} a (b :: k). (Typeable a, KnownIsoT a) => TypeDocMichelsonRep b #
mdTocFromRef :: (DocItem d, DocItemReferenced d ~ 'True) => HeaderLevel -> Markdown -> d -> Markdown #