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

Lorentz.Doc

Synopsis

Documentation

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

Put a document item.

docGroup :: 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

data DocElem d #

Constructors

DocElem 

Fields

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

Minimal complete definition

docItemPos, docItemSectionName, docItemToMarkdown

Associated Types

type DocItemPlacement d :: DocItemPlacementKind #

type DocItemReferenced d :: DocItemReferencedKind #

Instances

Instances details
DocItem DStorageType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DStorageType :: DocItemPlacementKind #

type DocItemReferenced DStorageType :: DocItemReferencedKind #

Methods

docItemPos :: Natural #

docItemSectionName :: Maybe Text #

docItemSectionDescription :: Maybe Markdown #

docItemSectionNameStyle :: DocSectionNameStyle #

docItemRef :: DStorageType -> DocItemRef (DocItemPlacement DStorageType) (DocItemReferenced DStorageType) #

docItemToMarkdown :: HeaderLevel -> DStorageType -> Markdown #

docItemToToc :: HeaderLevel -> DStorageType -> Markdown #

docItemDependencies :: DStorageType -> [SomeDocDefinitionItem] #

docItemsOrder :: [DStorageType] -> [DStorageType] #

DocItem DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DType :: DocItemPlacementKind #

type DocItemReferenced DType :: DocItemReferencedKind #

DocItem DGitRevision 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DGitRevision :: DocItemPlacementKind #

type DocItemReferenced DGitRevision :: DocItemReferencedKind #

DocItem DAnchor 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DAnchor :: DocItemPlacementKind #

type DocItemReferenced DAnchor :: DocItemReferencedKind #

DocItem DComment 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DComment :: DocItemPlacementKind #

type DocItemReferenced DComment :: DocItemReferencedKind #

DocItem DConversionInfo 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DConversionInfo :: DocItemPlacementKind #

type DocItemReferenced DConversionInfo :: DocItemReferencedKind #

Methods

docItemPos :: Natural #

docItemSectionName :: Maybe Text #

docItemSectionDescription :: Maybe Markdown #

docItemSectionNameStyle :: DocSectionNameStyle #

docItemRef :: DConversionInfo -> DocItemRef (DocItemPlacement DConversionInfo) (DocItemReferenced DConversionInfo) #

docItemToMarkdown :: HeaderLevel -> DConversionInfo -> Markdown #

docItemToToc :: HeaderLevel -> DConversionInfo -> Markdown #

docItemDependencies :: DConversionInfo -> [SomeDocDefinitionItem] #

docItemsOrder :: [DConversionInfo] -> [DConversionInfo] #

DocItem DDescription 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DDescription :: DocItemPlacementKind #

type DocItemReferenced DDescription :: DocItemReferencedKind #

DocItem DGeneralInfoSection 
Instance details

Defined in Michelson.Doc

DocItem DName 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DName :: DocItemPlacementKind #

type DocItemReferenced DName :: DocItemReferencedKind #

DocItem DToc 
Instance details

Defined in Michelson.Doc

Associated Types

type DocItemPlacement DToc :: DocItemPlacementKind #

type DocItemReferenced DToc :: DocItemReferencedKind #

DocItem DEntrypointExample Source # 
Instance details

Defined in Lorentz.Doc

DocItem DHashAlgorithm Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type DocItemPlacement DHashAlgorithm :: DocItemPlacementKind #

type DocItemReferenced DHashAlgorithm :: DocItemReferencedKind #

DocItem DEntrypointArg Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Associated Types

type DocItemPlacement DEntrypointArg :: DocItemPlacementKind #

type DocItemReferenced DEntrypointArg :: DocItemReferencedKind #

DocItem DEntrypointReference Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

DocItem DThrows Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type DocItemPlacement DThrows :: DocItemPlacementKind #

type DocItemReferenced DThrows :: DocItemReferencedKind #

DocItem DError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type DocItemPlacement DError :: DocItemPlacementKind #

type DocItemReferenced DError :: DocItemReferencedKind #

DocItem DDescribeErrorTagMap Source # 
Instance details

Defined in Lorentz.Errors.Numeric.Doc

EntrypointKindHasDoc ep => DocItem (DEntrypoint ep) Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Associated Types

type DocItemPlacement (DEntrypoint ep) :: DocItemPlacementKind #

type DocItemReferenced (DEntrypoint ep) :: DocItemReferencedKind #

newtype DocItemId #

Constructors

DocItemId Text 

Instances

Instances details
Eq DocItemId 
Instance details

Defined in Michelson.Doc

Ord DocItemId 
Instance details

Defined in Michelson.Doc

Show DocItemId 
Instance details

Defined in Michelson.Doc

ToAnchor DocItemId 
Instance details

Defined in Michelson.Doc

Methods

toAnchor :: DocItemId -> Anchor

newtype DocItemPos #

Constructors

DocItemPos (Natural, Text) 

Instances

Instances details
Eq DocItemPos 
Instance details

Defined in Michelson.Doc

Ord DocItemPos 
Instance details

Defined in Michelson.Doc

Show DocItemPos 
Instance details

Defined in Michelson.Doc

Buildable DocItemPos 
Instance details

Defined in Michelson.Doc

Methods

build :: DocItemPos -> Builder #

data DocItemRef (p :: DocItemPlacementKind) (r :: DocItemReferencedKind) where #

Instances

Instances details
ToAnchor (DocItemRef d 'True) 
Instance details

Defined in Michelson.Doc

Methods

toAnchor :: DocItemRef d 'True -> Anchor

data DocSection #

Constructors

DocItem d => DocSection (NonEmpty $ DocElem d) 

Instances

Instances details
Show DocSection 
Instance details

Defined in Michelson.Doc

data SomeDocItem where #

Constructors

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

Instances

Instances details
Show SomeDocItem 
Instance details

Defined in Michelson.Doc

Show DocGrouping 
Instance details

Defined in Michelson.Doc

NFData SomeDocItem 
Instance details

Defined in Michelson.Doc

Methods

rnf :: SomeDocItem -> () #

newtype SubDoc #

Constructors

SubDoc DocBlock 

Instances

Instances details
Show DocGrouping 
Instance details

Defined in Michelson.Doc

di ~ DName => IsString (SubDoc -> di) 
Instance details

Defined in Michelson.Doc

Methods

fromString :: String -> SubDoc -> di #

newtype GitRepoSettings #

Constructors

GitRepoSettings 

Fields

data DType where #

Constructors

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

Instances

Instances details
Eq DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

(==) :: DType -> DType -> Bool #

(/=) :: DType -> DType -> Bool #

Ord DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

compare :: DType -> DType -> Ordering #

(<) :: DType -> DType -> Bool #

(<=) :: DType -> DType -> Bool #

(>) :: DType -> DType -> Bool #

(>=) :: DType -> DType -> Bool #

max :: DType -> DType -> DType #

min :: DType -> DType -> DType #

Show DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

DocItem DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DType :: DocItemPlacementKind #

type DocItemReferenced DType :: DocItemReferencedKind #

type DocItemPlacement DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemReferenced DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

subDocToMarkdown :: HeaderLevel -> SubDoc -> Markdown #

class ContainsDoc a where #

Instances

Instances details
ContainsDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

ContainsDoc (Contract cp st) Source # 
Instance details

Defined in Lorentz.Run

class ContainsDoc a => ContainsUpdateableDoc a where #

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> a -> a #

Instances

Instances details
ContainsUpdateableDoc (i :-> o) Source # 
Instance details

Defined in Lorentz.Doc

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o #

ContainsUpdateableDoc (Contract cp st) Source # 
Instance details

Defined in Lorentz.Run

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st -> Contract cp st #

modifyDoc :: (ContainsUpdateableDoc a, DocItem i1, DocItem i2) => (i1 -> Maybe i2) -> a -> a #

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

Minimal complete definition

typeDocMdDescription

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

Instances details
TypeHasDoc Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Bool :: FieldDescriptions #

TypeHasDoc Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Integer :: FieldDescriptions #

TypeHasDoc Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Natural :: FieldDescriptions #

TypeHasDoc () 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions () :: FieldDescriptions #

Methods

typeDocName :: Proxy () -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy () -> WithinParens -> Markdown #

typeDocDependencies :: Proxy () -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep () #

typeDocMichelsonRep :: TypeDocMichelsonRep () #

TypeHasDoc ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ByteString :: FieldDescriptions #

TypeHasDoc MText 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions MText :: FieldDescriptions #

TypeHasDoc Operation 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Operation :: FieldDescriptions #

TypeHasDoc EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions EpAddress :: FieldDescriptions #

TypeHasDoc Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Address :: FieldDescriptions #

TypeHasDoc ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChainId :: FieldDescriptions #

TypeHasDoc KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions KeyHash :: FieldDescriptions #

TypeHasDoc Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Mutez :: FieldDescriptions #

TypeHasDoc PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions PublicKey :: FieldDescriptions #

TypeHasDoc Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Signature :: FieldDescriptions #

TypeHasDoc Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Timestamp :: FieldDescriptions #

TypeHasDoc Empty Source # 
Instance details

Defined in Lorentz.Empty

Associated Types

type TypeDocFieldDescriptions Empty :: FieldDescriptions #

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

Defined in Michelson.Typed.Haskell.Doc

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] #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Maybe a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Maybe a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Maybe a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Maybe a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Maybe a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Maybe a) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Set a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Set a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Set a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Set a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Set a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Set a) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (ContractRef cp) :: FieldDescriptions #

TypeHasDoc p => TypeHasDoc (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

TypeHasDoc a => TypeHasDoc (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (TSignature a) :: FieldDescriptions #

TypeHasDoc a => TypeHasDoc (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (Packed a) :: FieldDescriptions #

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

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (VoidResult r) :: FieldDescriptions #

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

Defined in Lorentz.UParam

Associated Types

type TypeDocFieldDescriptions (UParam interface) :: FieldDescriptions #

Methods

typeDocName :: Proxy (UParam interface) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (UParam interface) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (UParam interface) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (UParam interface) #

typeDocMichelsonRep :: TypeDocMichelsonRep (UParam interface) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Either l r) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Either l r) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Either l r) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Either l r) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Either l r) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Either l r) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (a, b) :: FieldDescriptions #

Methods

typeDocName :: Proxy (a, b) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (a, b) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (a, b) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (a, b) #

typeDocMichelsonRep :: TypeDocMichelsonRep (a, b) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Map k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Map k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Map k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Map k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Map k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Map k v) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (BigMap k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (BigMap k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (BigMap k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (BigMap k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (BigMap k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (BigMap k v) #

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

Defined in Lorentz.Doc

Associated Types

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

Methods

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) #

TypeHasDoc p => TypeHasDoc (TAddress p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (TAddress p) :: FieldDescriptions #

(KnownHashAlgorithm alg, TypeHasDoc a) => TypeHasDoc (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (Hash alg a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Hash alg a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Hash alg a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Hash alg a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Hash alg a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Hash alg a) #

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

Defined in Lorentz.Extensible

Associated Types

type TypeDocFieldDescriptions (Extensible x) :: FieldDescriptions #

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

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (Void_ a r) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Void_ a r) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Void_ a r) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Void_ a r) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Void_ a r) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Void_ a r) #

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

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (View a r) :: FieldDescriptions #

Methods

typeDocName :: Proxy (View a r) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (View a r) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (View a r) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (View a r) #

typeDocMichelsonRep :: TypeDocMichelsonRep (View a r) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

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

typeDocMdDescription :: Markdown #

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

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

typeDocHaskellRep :: TypeDocHaskellRep (a, b, c) #

typeDocMichelsonRep :: TypeDocMichelsonRep (a, b, c) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

typeDocName :: Proxy (NamedF f a n) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (NamedF f a n) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (NamedF f a n) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (NamedF f a n) #

typeDocMichelsonRep :: TypeDocMichelsonRep (NamedF f a n) #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

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

typeDocMdDescription :: Markdown #

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

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

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

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

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

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

typeDocMdDescription :: Markdown #

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

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

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

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

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

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

typeDocMdDescription :: Markdown #

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

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

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

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

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

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

Methods

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

typeDocMdDescription :: Markdown #

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

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

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

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

data SomeTypeWithDoc where #

Constructors

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

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

Instances

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

class IsHomomorphic (a :: k) #

Instances

Instances details
IsHomomorphic (a :: k) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

customTypeDocMdReference :: (Text, DType) -> [DType] -> 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

TypeHasDoc p => TypeHasDoc (FutureContract p) Source # 
Instance details

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

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

Associated Types

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

Methods

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) #

TypeHasDoc p => TypeHasDoc (TAddress p) Source # 
Instance details

Associated Types

type TypeDocFieldDescriptions (TAddress p) :: FieldDescriptions #

ContainsDoc (i :-> o) Source # 
Instance details

ContainsUpdateableDoc (i :-> o) Source # 
Instance details

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> (i :-> o) -> i :-> o #