Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- doc :: DocItem di => di -> s :-> s
- docGroup :: DocGrouping -> (inp :-> out) -> inp :-> out
- 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
- 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
- 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 :: 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.
buildLorentzDoc :: (inp :-> out) -> ContractDoc Source #
buildLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> ContractDoc Source #
renderLorentzDoc :: (inp :-> out) -> LText Source #
renderLorentzDocWithGitRev :: DGitRevision -> (inp :-> out) -> LText Source #
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
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
Eq DocItemId | |
Ord DocItemId | |
Defined in Michelson.Doc | |
Show DocItemId | |
ToAnchor DocItemId | |
Defined in Michelson.Doc |
newtype DocItemPos #
Instances
Eq DocItemPos | |
Defined in Michelson.Doc (==) :: DocItemPos -> DocItemPos -> Bool # (/=) :: DocItemPos -> DocItemPos -> Bool # | |
Ord DocItemPos | |
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 | |
Defined in Michelson.Doc showsPrec :: Int -> DocItemPos -> ShowS # show :: DocItemPos -> String # showList :: [DocItemPos] -> ShowS # | |
Buildable DocItemPos | |
Defined in Michelson.Doc build :: DocItemPos -> Builder # |
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 Michelson.Doc toAnchor :: DocItemRef d 'True -> Anchor |
data DocSection #
DocItem d => DocSection (NonEmpty $ DocElem d) |
Instances
Show DocSection | |
Defined in Michelson.Doc showsPrec :: Int -> DocSection -> ShowS # show :: DocSection -> String # showList :: [DocSection] -> ShowS # |
data SomeDocItem where #
SomeDocItem :: forall d. DocItem d => d -> SomeDocItem |
Instances
Show SomeDocItem | |
Defined in Michelson.Doc showsPrec :: Int -> SomeDocItem -> ShowS # show :: SomeDocItem -> String # showList :: [SomeDocItem] -> ShowS # | |
Show DocGrouping | |
Defined in Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # | |
NFData SomeDocItem | |
Defined in Michelson.Doc rnf :: SomeDocItem -> () # |
data SomeDocDefinitionItem where #
SomeDocDefinitionItem :: forall d. (DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) => d -> SomeDocDefinitionItem |
Instances
Eq SomeDocDefinitionItem | |
Defined in Michelson.Doc (==) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # (/=) :: SomeDocDefinitionItem -> SomeDocDefinitionItem -> Bool # | |
Ord SomeDocDefinitionItem | |
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 # |
SubDoc DocBlock |
Instances
Show DocGrouping | |
Defined in Michelson.Doc showsPrec :: Int -> DocGrouping -> ShowS # show :: DocGrouping -> String # showList :: [DocGrouping] -> ShowS # |
type DocGrouping = SubDoc -> SomeDocItem #
data ContractDoc #
ContractDoc | |
|
Instances
Semigroup ContractDoc | |
Defined in Michelson.Doc (<>) :: ContractDoc -> ContractDoc -> ContractDoc # sconcat :: NonEmpty ContractDoc -> ContractDoc # stimes :: Integral b => b -> ContractDoc -> ContractDoc # | |
Monoid ContractDoc | |
Defined in Michelson.Doc mempty :: ContractDoc # mappend :: ContractDoc -> ContractDoc -> ContractDoc # mconcat :: [ContractDoc] -> ContractDoc # |
data DDescription #
Instances
DocItem DDescription | |
Defined in 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 Michelson.Doc | |
type DocItemReferenced DDescription | |
Defined in 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 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 Michelson.Doc | |
type DocItemReferenced DGitRevision | |
Defined in Michelson.Doc |
newtype GitRepoSettings #
mkDGitRevision :: ExpQ #
Instances
DocItem DComment | |
Defined in 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 Michelson.Doc | |
type DocItemReferenced DComment | |
Defined in Michelson.Doc |
DAnchor Anchor |
Instances
DocItem DAnchor | |
Defined in 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 Michelson.Doc | |
type DocItemReferenced DAnchor | |
Defined in Michelson.Doc |
DType :: forall a. TypeHasDoc a => Proxy a -> DType |
Instances
Eq DType | |
Ord DType | |
Show DType | |
DocItem DType | |
Defined in 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] # | |
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 #
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
data SomeTypeWithDoc where #
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 #
Orphan instances
Each '[Typeable :: [Type] -> Constraint, ReifyList TypeHasDoc] '[i, o] => TypeHasDoc (i :-> o) Source # | |
type TypeDocFieldDescriptions (i :-> o) :: FieldDescriptions # typeDocName :: Proxy (i :-> o) -> Text # typeDocMdDescription :: Markdown # typeDocMdReference :: Proxy (i :-> o) -> WithinParens -> Markdown # typeDocDependencies :: Proxy (i :-> o) -> [SomeDocDefinitionItem] # typeDocHaskellRep :: TypeDocHaskellRep (i :-> o) # typeDocMichelsonRep :: TypeDocMichelsonRep (i :-> o) # |