lorentz-0.16.0: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
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 #

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

data DView Source #

Renders to a view section.

Constructors

DView 

Fields

data DViewDesc Source #

Renders to documentation of view descriptor.

Constructors

forall vd.ViewsDescriptorHasDoc vd => DViewDesc (Proxy vd) 

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.

Minimal complete definition

Nothing

Methods

viewsDescriptorName :: Proxy vd -> Text Source #

default viewsDescriptorName :: (Generic vd, KnownSymbol (GenericTypeName vd)) => Proxy vd -> Text Source #

renderViewsDescriptorDoc :: Proxy vd -> Doc Source #

Re-exports

type Markdown = Doc #

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 DHashAlgorithm Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type DocItemPlacement DHashAlgorithm :: DocItemPlacementKind #

type DocItemReferenced DHashAlgorithm :: DocItemReferencedKind #

DocItem DEntrypointExample Source # 
Instance details

Defined in Lorentz.Doc

DocItem DView Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type DocItemPlacement DView :: DocItemPlacementKind #

type DocItemReferenced DView :: DocItemReferencedKind #

DocItem DViewArg Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type DocItemPlacement DViewArg :: DocItemPlacementKind #

type DocItemReferenced DViewArg :: DocItemReferencedKind #

DocItem DViewDesc Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type DocItemPlacement DViewDesc :: DocItemPlacementKind #

type DocItemReferenced DViewDesc :: DocItemReferencedKind #

DocItem DViewRet Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type DocItemPlacement DViewRet :: DocItemPlacementKind #

type DocItemReferenced DViewRet :: 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 DError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type DocItemPlacement DError :: DocItemPlacementKind #

type DocItemReferenced DError :: DocItemReferencedKind #

DocItem DThrows Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type DocItemPlacement DThrows :: DocItemPlacementKind #

type DocItemReferenced DThrows :: DocItemReferencedKind #

DocItem DDescribeErrorTagMap Source # 
Instance details

Defined in Lorentz.Errors.Numeric.Doc

DocItem DAnchor 
Instance details

Defined in Morley.Michelson.Doc

Associated Types

type DocItemPlacement DAnchor :: DocItemPlacementKind #

type DocItemReferenced DAnchor :: DocItemReferencedKind #

DocItem DComment 
Instance details

Defined in Morley.Michelson.Doc

Associated Types

type DocItemPlacement DComment :: DocItemPlacementKind #

type DocItemReferenced DComment :: DocItemReferencedKind #

DocItem DConversionInfo 
Instance details

Defined in Morley.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 Morley.Michelson.Doc

Associated Types

type DocItemPlacement DDescription :: DocItemPlacementKind #

type DocItemReferenced DDescription :: DocItemReferencedKind #

DocItem DGeneralInfoSection 
Instance details

Defined in Morley.Michelson.Doc

DocItem DGitRevision 
Instance details

Defined in Morley.Michelson.Doc

Associated Types

type DocItemPlacement DGitRevision :: DocItemPlacementKind #

type DocItemReferenced DGitRevision :: DocItemReferencedKind #

DocItem DName 
Instance details

Defined in Morley.Michelson.Doc

Associated Types

type DocItemPlacement DName :: DocItemPlacementKind #

type DocItemReferenced DName :: DocItemReferencedKind #

DocItem DToc 
Instance details

Defined in Morley.Michelson.Doc

Associated Types

type DocItemPlacement DToc :: DocItemPlacementKind #

type DocItemReferenced DToc :: DocItemReferencedKind #

DocItem DStorageType 
Instance details

Defined in Morley.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 Morley.Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DType :: DocItemPlacementKind #

type DocItemReferenced DType :: DocItemReferencedKind #

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
Show DocItemId 
Instance details

Defined in Morley.Michelson.Doc

Eq DocItemId 
Instance details

Defined in Morley.Michelson.Doc

Ord DocItemId 
Instance details

Defined in Morley.Michelson.Doc

ToAnchor DocItemId 
Instance details

Defined in Morley.Michelson.Doc

Methods

toAnchor :: DocItemId -> Anchor

newtype DocItemPos #

Constructors

DocItemPos (Natural, Text) 

Instances

Instances details
Show DocItemPos 
Instance details

Defined in Morley.Michelson.Doc

Eq DocItemPos 
Instance details

Defined in Morley.Michelson.Doc

Ord DocItemPos 
Instance details

Defined in Morley.Michelson.Doc

Buildable DocItemPos 
Instance details

Defined in Morley.Michelson.Doc

Methods

build :: DocItemPos -> Doc

buildList :: [DocItemPos] -> Doc

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

Instances

Instances details
ToAnchor (DocItemRef d 'True) 
Instance details

Defined in Morley.Michelson.Doc

Methods

toAnchor :: DocItemRef d 'True -> Anchor

data DocSection #

Constructors

DocItem d => DocSection (NonEmpty $ DocElem d) 

data SomeDocItem where #

Constructors

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

Instances

Instances details
Show DocGrouping 
Instance details

Defined in Morley.Michelson.Doc

Show SomeDocItem 
Instance details

Defined in Morley.Michelson.Doc

NFData SomeDocItem 
Instance details

Defined in Morley.Michelson.Doc

Methods

rnf :: SomeDocItem -> () #

newtype SubDoc #

Constructors

SubDoc DocBlock 

Instances

Instances details
Show DocGrouping 
Instance details

Defined in Morley.Michelson.Doc

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

Defined in Morley.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 Morley.Michelson.Typed.Haskell.Doc

Methods

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

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

Ord DType 
Instance details

Defined in Morley.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 #

DocItem DType 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type DocItemPlacement DType :: DocItemPlacementKind #

type DocItemReferenced DType :: DocItemReferencedKind #

Buildable DType 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Methods

build :: DType -> Doc

buildList :: [DType] -> Doc

type DocItemPlacement DType 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type DocItemReferenced DType 
Instance details

Defined in Morley.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 (ContractCode i o) Source # 
Instance details

Defined in Lorentz.Doc

ContainsDoc (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Doc

ContainsDoc (ContractData cp st vd) 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 (ContractCode i o) Source # 
Instance details

Defined in Lorentz.Doc

ContainsUpdateableDoc (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Doc

Methods

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

ContainsUpdateableDoc (ContractData cp st vd) Source # 
Instance details

Defined in Lorentz.Run

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> ContractData cp st vd -> ContractData cp st vd #

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 ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ByteString :: FieldDescriptions #

TypeHasDoc Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type TypeDocFieldDescriptions Never :: FieldDescriptions #

TypeHasDoc OpenChest Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type TypeDocFieldDescriptions OpenChest :: FieldDescriptions #

TypeHasDoc MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions MText :: FieldDescriptions #

TypeHasDoc Operation 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Operation :: FieldDescriptions #

TypeHasDoc EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions EpAddress :: FieldDescriptions #

TypeHasDoc Address 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Address :: FieldDescriptions #

TypeHasDoc ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChainId :: FieldDescriptions #

TypeHasDoc Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Mutez :: FieldDescriptions #

TypeHasDoc Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Timestamp :: FieldDescriptions #

TypeHasDoc KeyHash 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions KeyHash :: FieldDescriptions #

TypeHasDoc PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions PublicKey :: FieldDescriptions #

TypeHasDoc Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Signature :: FieldDescriptions #

TypeHasDoc Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Chest :: FieldDescriptions #

TypeHasDoc ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChestKey :: FieldDescriptions #

TypeHasDoc Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Integer :: FieldDescriptions #

TypeHasDoc Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Natural :: FieldDescriptions #

TypeHasDoc () 
Instance details

Defined in Morley.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 Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Bool :: FieldDescriptions #

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

Defined in Morley.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) #

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

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

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

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (ChestT a) :: FieldDescriptions #

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

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (OpenChestT a) :: FieldDescriptions #

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

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (Packed a) :: FieldDescriptions #

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

Defined in Lorentz.Bytes

Associated Types

type TypeDocFieldDescriptions (TSignature a) :: FieldDescriptions #

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

Defined in Lorentz.Macro

Associated Types

type TypeDocFieldDescriptions (VoidResult r) :: FieldDescriptions #

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

Defined in Lorentz.Range

Associated Types

type TypeDocFieldDescriptions (Range a) :: FieldDescriptions #

Methods

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

typeDocMdDescription :: Markdown #

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

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

typeDocHaskellRep :: TypeDocHaskellRep (Range a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Range a) #

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

Defined in Lorentz.Range

Associated Types

type TypeDocFieldDescriptions (RangeEE a) :: FieldDescriptions #

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

Defined in Lorentz.Range

Associated Types

type TypeDocFieldDescriptions (RangeEI a) :: FieldDescriptions #

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

Defined in Lorentz.Range

Associated Types

type TypeDocFieldDescriptions (RangeFailureInfo a) :: FieldDescriptions #

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

Defined in Lorentz.Range

Associated Types

type TypeDocFieldDescriptions (RangeIE a) :: 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 '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (ContractRef cp) :: FieldDescriptions #

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

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Ticket a) :: FieldDescriptions #

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

Defined in Morley.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) #

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

Defined in Morley.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 '[l, r] => TypeHasDoc (Either l r) 
Instance details

Defined in Morley.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) #

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

Defined in Morley.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) #

(TypeHasDoc p, ViewsDescriptorHasDoc vd) => TypeHasDoc (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (TAddress p vd) :: FieldDescriptions #

Methods

typeDocName :: Proxy (TAddress p vd) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (TAddress p vd) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (TAddress p vd) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (TAddress p vd) #

typeDocMichelsonRep :: TypeDocMichelsonRep (TAddress p vd) #

(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, ReifyList TypeHasDoc] '[i, o] => TypeHasDoc (WrappedLambda i o) Source # 
Instance details

Defined in Lorentz.Lambda

Associated Types

type TypeDocFieldDescriptions (WrappedLambda i o) :: FieldDescriptions #

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

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

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

Defined in Morley.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) #

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

Defined in Morley.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) #

(Typeable k, Typeable action, TypeHasDoc td) => TypeHasDoc (STicket action td) Source # 
Instance details

Defined in Lorentz.Tickets

Associated Types

type TypeDocFieldDescriptions (STicket action td) :: FieldDescriptions #

Methods

typeDocName :: Proxy (STicket action td) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (STicket action td) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (STicket action td) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (STicket action td) #

typeDocMichelsonRep :: TypeDocMichelsonRep (STicket action td) #

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

Defined in Morley.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] => TypeHasDoc (a, b, c) 
Instance details

Defined in Morley.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) #

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

Defined in Morley.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 Morley.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 Morley.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 Morley.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) #

class TypeHasFieldNamingStrategy (a :: k) where #

Minimal complete definition

Nothing

Instances

Instances details
TypeHasFieldNamingStrategy FieldCamelCase 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

TypeHasFieldNamingStrategy FieldSnakeCase 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

TypeHasFieldNamingStrategy (a :: k) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

TypeHasFieldNamingStrategy (RangeFailureInfo a :: Type) Source # 
Instance details

Defined in Lorentz.Range

data SomeTypeWithDoc where #

Constructors

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

type family HaveCommonTypeCtor (a :: k) (b :: k) where ... #

Equations

HaveCommonTypeCtor (ac _1 :: k2) (bc _2 :: k2) = HaveCommonTypeCtor ac bc 
HaveCommonTypeCtor (a :: k) (a :: k) = () 

class IsHomomorphic (a :: k) #

Instances

Instances details
IsHomomorphic (a :: k) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

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

Defined in Morley.Michelson.Typed.Haskell.Doc

genericTypeDocDependencies :: (Generic a, GTypeHasDoc (GRep a)) => Proxy a -> [SomeDocDefinitionItem] #

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

Orphan instances

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

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

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

ContainsDoc (ContractCode i o) Source # 
Instance details

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

Methods

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

ContainsUpdateableDoc (ContractCode i o) Source # 
Instance details

(TypeHasDoc p, ViewsDescriptorHasDoc vd) => TypeHasDoc (TAddress p vd) Source # 
Instance details

Associated Types

type TypeDocFieldDescriptions (TAddress p vd) :: FieldDescriptions #

Methods

typeDocName :: Proxy (TAddress p vd) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (TAddress p vd) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (TAddress p vd) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (TAddress p vd) #

typeDocMichelsonRep :: TypeDocMichelsonRep (TAddress p vd) #

ContainsDoc (Contract cp st vd) Source # 
Instance details

ContainsUpdateableDoc (Contract cp st vd) Source # 
Instance details

Methods

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