Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation of types appearing in contracts.
Synopsis
- type ADTRep a = [ConstructorRep a]
- data ConstructorRep a = ConstructorRep {}
- crNameL :: forall a. Lens' (ConstructorRep a) Text
- crDescriptionL :: forall a. Lens' (ConstructorRep a) (Maybe Text)
- crFieldsL :: forall a a. Lens (ConstructorRep a) (ConstructorRep a) [FieldRep a] [FieldRep a]
- data FieldRep a = FieldRep {}
- frNameL :: forall a. Lens' (FieldRep a) (Maybe Text)
- frDescriptionL :: forall a. Lens' (FieldRep a) (Maybe Text)
- frTypeRepL :: forall a a. Lens (FieldRep a) (FieldRep a) a a
- newtype WithinParens = WithinParens Bool
- 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 where
- typeFieldNamingStrategy :: Text -> Text
- data FieldCamelCase
- data FieldSnakeCase
- type TypeDocHaskellRep a = Proxy a -> FieldDescriptionsV -> Maybe (Maybe DocTypeRepLHS, ADTRep SomeTypeWithDoc)
- type TypeDocMichelsonRep a = Proxy a -> (Maybe DocTypeRepLHS, T)
- type FieldDescriptions = [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
- type PolyTypeHasDocC ts = Each '[TypeHasDoc] ts
- data SomeTypeWithDoc where
- SomeTypeWithDoc :: TypeHasDoc td => Proxy td -> SomeTypeWithDoc
- typeDocBuiltMichelsonRep :: TypeHasDoc a => Proxy a -> Doc
- type family HaveCommonTypeCtor a b where ...
- class IsHomomorphic a
- genericTypeDocDependencies :: forall a. (Generic a, GTypeHasDoc (GRep a)) => Proxy a -> [SomeDocDefinitionItem]
- customTypeDocMdReference :: (Text, DType) -> [DType] -> WithinParens -> Markdown
- customTypeDocMdReference' :: (Text, DType) -> [WithinParens -> Markdown] -> WithinParens -> Markdown
- homomorphicTypeDocMdReference :: forall (t :: Type). (Typeable t, TypeHasDoc t, IsHomomorphic t) => Proxy t -> WithinParens -> Markdown
- poly1TypeDocMdReference :: forall t (r :: Type) (a :: Type). (r ~ t a, Typeable t, Each '[TypeHasDoc] [r, a], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown
- poly2TypeDocMdReference :: forall t (r :: Type) (a :: Type) (b :: Type). (r ~ t a b, Typeable t, Each '[TypeHasDoc] [r, a, b], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown
- homomorphicTypeDocHaskellRep :: forall a. (Generic a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep a
- concreteTypeDocHaskellRep :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b
- unsafeConcreteTypeDocHaskellRep :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep b
- haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepMap :: (Text -> Text) -> TypeDocHaskellRep a -> TypeDocHaskellRep a
- haskellRepAdjust :: (Maybe Text -> Maybe Text) -> TypeDocHaskellRep a -> TypeDocHaskellRep a
- homomorphicTypeDocMichelsonRep :: forall a. KnownIsoT a => TypeDocMichelsonRep a
- concreteTypeDocMichelsonRep :: forall a b. (Typeable a, KnownIsoT a, HaveCommonTypeCtor b a) => TypeDocMichelsonRep b
- unsafeConcreteTypeDocMichelsonRep :: forall a b. (Typeable a, KnownIsoT a) => TypeDocMichelsonRep b
- data DType where
- DType :: TypeHasDoc a => Proxy a -> DType
- newtype DStorageType = DStorageType DType
- dStorage :: forall store. TypeHasDoc store => DStorageType
- class GTypeHasDoc (x :: Type -> Type)
- class GProductHasDoc (x :: Type -> Type)
- dTypeDep :: forall (t :: Type). TypeHasDoc t => SomeDocDefinitionItem
- dTypeDepP :: forall (t :: Type). TypeHasDoc t => Proxy t -> SomeDocDefinitionItem
- buildADTRep :: forall a. (WithinParens -> a -> Markdown) -> ADTRep a -> Markdown
- applyWithinParens :: WithinParens -> Markdown -> Markdown
- buildTypeWithinParens :: forall a. Typeable a => WithinParens -> Markdown
Documentation
type ADTRep a = [ConstructorRep a] Source #
Stands for representation of some Haskell ADT corresponding to
Michelson value. Type parameter a
is what you put in place of
each field of the datatype, e.g. information about field type.
This representation also includes descriptions of constructors and fields.
data ConstructorRep a Source #
Representation of a constructor with an optional description.
crDescriptionL :: forall a. Lens' (ConstructorRep a) (Maybe Text) Source #
crFieldsL :: forall a a. Lens (ConstructorRep a) (ConstructorRep a) [FieldRep a] [FieldRep a] Source #
Representation of a field with an optional description.
newtype WithinParens Source #
Whether given text should be rendered grouped in parentheses (if they make sense).
class (Typeable a, SingI (TypeDocFieldDescriptions a), FieldDescriptionsValid (TypeDocFieldDescriptions a) a) => TypeHasDoc a where Source #
Description for a Haskell type appearing in documentation.
Generic-deriving instance produces a custom error when Generic
is missing:
>>>
data Foo = Foo () deriving TypeHasDoc
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo () deriving Generic
>>>
instance TypeHasDoc Foo where typeDocMdDescription = "Foo"
... ... No instance for (IsoValue Foo) ...
>>>
data Foo = Foo () deriving (Generic, IsoValue)
>>>
instance TypeHasDoc Foo where typeDocMdDescription = "Foo"
type TypeDocFieldDescriptions a :: FieldDescriptions Source #
Description of constructors and fields of a
.
See FieldDescriptions
documentation for an example of usage.
Descriptions will be checked at compile time to make sure that only existing constructors and fields are referenced.
For that check to work instance Generic a
is required whenever TypeDocFieldDescriptions
is not empty.
For implementation of the check see FieldDescriptionsValid
type family.
type TypeDocFieldDescriptions _ = '[]
typeDocName :: Proxy a -> Text Source #
Name of type as it appears in definitions section.
Each type must have its own unique name because it will be used in identifier for references.
Default definition derives name from Generics. If it does not fit, consider defining this function manually. (We tried using Data.Data for this, but it produces names including module names which is not do we want).
default typeDocName :: (Generic a, KnownSymbol (GenericTypeName a)) => Proxy a -> Text Source #
typeDocMdDescription :: Markdown Source #
Explanation of a type. Markdown formatting is allowed.
typeDocMdReference :: Proxy a -> WithinParens -> Markdown Source #
How reference to this type is rendered, in Markdown.
Examples:
[Integer](#type-integer)
,[Maybe](#type-Maybe) [()](#type-unit)
.
Consider using one of the following functions as default implementation; which one to use depends on number of type arguments in your type:
If none of them fits your purposes precisely, consider using
customTypeDocMdReference
.
default typeDocMdReference :: (Typeable a, IsHomomorphic a) => Proxy a -> WithinParens -> Markdown Source #
typeDocDependencies :: Proxy a -> [SomeDocDefinitionItem] Source #
All types which this type directly contains.
Used in automatic types discovery.
default typeDocDependencies :: (Generic a, GTypeHasDoc (GRep a)) => Proxy a -> [SomeDocDefinitionItem] Source #
typeDocHaskellRep :: TypeDocHaskellRep a Source #
For complex types - their immediate Haskell representation.
For primitive types set this to Nothing
.
For homomorphic types use homomorphicTypeDocHaskellRep
implementation.
For polymorphic types consider using concreteTypeDocHaskellRep
as implementation.
Modifier haskellRepNoFields
can be used to hide names of fields,
beneficial for newtypes.
Use haskellRepAdjust
or haskellRepMap
for more involved adjustments.
Also, consider defining an instance of TypeHasFieldNamingStrategy
instead
of defining this method -- the former can be used downstream, e.g. in
lorentz, for better naming consistency.
default typeDocHaskellRep :: (Generic a, GTypeHasDoc (GRep a), IsHomomorphic a, TypeHasFieldNamingStrategy a) => TypeDocHaskellRep a Source #
typeDocMichelsonRep :: TypeDocMichelsonRep a Source #
Final michelson representation of a type.
For homomorphic types use homomorphicTypeDocMichelsonRep
implementation.
For polymorphic types consider using concreteTypeDocMichelsonRep
as implementation.
default typeDocMichelsonRep :: (KnownIsoT a, IsHomomorphic a) => TypeDocMichelsonRep a Source #
Instances
class TypeHasFieldNamingStrategy a where Source #
Field naming strategy used by a type. id
by default.
Some common options include: > typeFieldNamingStrategy = stripFieldPrefix > typeFieldNamingStrategy = toSnake . dropPrefix
This is used by the default implementation of typeDocHaskellRep
and
intended to be reused downstream.
You can also use DerivingVia
together with FieldCamelCase
and
FieldSnakeCase
to easily define instances of this class:
data MyType = ... deriving TypeHasFieldNamingStrategy via FieldCamelCase
Nothing
typeFieldNamingStrategy :: Text -> Text Source #
Instances
TypeHasFieldNamingStrategy FieldCamelCase Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text Source # | |
TypeHasFieldNamingStrategy FieldSnakeCase Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text Source # | |
TypeHasFieldNamingStrategy (a :: k) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc typeFieldNamingStrategy :: Text -> Text Source # |
data FieldCamelCase Source #
Empty datatype used as marker for DerivingVia
with
TypeHasFieldNamingStrategy
.
Uses stripFieldPrefix
strategy.
Instances
data FieldSnakeCase Source #
Empty datatype used as marker for DerivingVia
with
TypeHasFieldNamingStrategy
.
Uses
strategy.toSnake
. dropPrefix
Instances
type TypeDocHaskellRep a = Proxy a -> FieldDescriptionsV -> Maybe (Maybe DocTypeRepLHS, ADTRep SomeTypeWithDoc) Source #
Signature of typeDocHaskellRep
function.
A value of FieldDescriptionsV
is provided by the library to make sure that
instances won't replace it with an unchecked value.
When value is Just
, it contains types which this type is built from.
First element of provided pair may contain name a concrete type which has
the same type constructor as a
(or just a
for homomorphic types), and
the second element of the pair - its unfolding in Haskell.
For example, for some newtype MyNewtype = MyNewtype (Integer, Natural)
we would not specify the first element in the pair because MyNewtype
is
already a concrete type, and second element would contain (Integer, Natural)
.
For polymorphic types like newtype MyPolyNewtype a = MyPolyNewtype (Text, a)
,
we want to describe its representation on some example of a
, because
working with type variables is too non-trivial; so the first element of
the pair may be e.g. "MyPolyNewType Integer"
, and the second one shows
that it unfolds to (Text, Integer)
.
When rendered, values of this type look like:
(Integer, Natural)
- for homomorphic type.MyError Integer = (Text, Integer)
- concrete sample for polymorphic type.
type TypeDocMichelsonRep a = Proxy a -> (Maybe DocTypeRepLHS, T) Source #
Signature of typeDocMichelsonRep
function.
As in TypeDocHaskellRep
, set the first element of the pair to Nothing
for primitive types, otherwise it stands as some instantiation of a type,
and its Michelson representation is given in the second element of the pair.
Examples of rendered representation:
pair int nat
- for homomorphic type.MyError Integer = pair string int
- concrete sample for polymorphic type.
type FieldDescriptions = [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))] Source #
Description of constructors and fields of some datatype.
This type is just two nested maps represented as associative lists. It is supposed to be interpreted like this:
[(Constructor name, (Maybe constructor description, [(Field name, Field description)]))]
Example with a concrete data type:
data Foo = Foo { fFoo :: Int } | Bar { fBar :: Text } deriving (Generic) type FooDescriptions = '[ '( "Foo", '( 'Just "foo constructor", , '[ '("fFoo", "some number") ]) ) , '( "Bar", '( 'Nothing, , '[ '("fBar", "some string") ]) ) ]
type PolyTypeHasDocC ts = Each '[TypeHasDoc] ts Source #
Constraint, required when deriving TypeHasDoc
for polymorphic type
with the least possible number of methods defined manually.
data SomeTypeWithDoc where Source #
Data hides some type implementing TypeHasDoc
.
SomeTypeWithDoc :: TypeHasDoc td => Proxy td -> SomeTypeWithDoc |
typeDocBuiltMichelsonRep :: TypeHasDoc a => Proxy a -> Doc Source #
Fully render Michelson representation of a type.
Since this will be used in markdown, the type is forced to a single line.
>>>
data Foo = Foo () () () () () () () () () () () () deriving (Generic, IsoValue)
>>>
instance TypeHasDoc Foo where typeDocMdDescription = "Foo type"
>>>
typeDocBuiltMichelsonRep $ Proxy @Foo
**Final Michelson representation:** `pair (pair (pair unit unit unit) unit unit unit) (pair unit unit unit) unit unit unit`
type family HaveCommonTypeCtor a b where ... Source #
Require two types to be built from the same type constructor.
E.g. HaveCommonTypeCtor (Maybe Integer) (Maybe Natural)
is defined,
while HaveCommonTypeCtor (Maybe Integer) [Integer]
is not.
HaveCommonTypeCtor (ac _) (bc _) = HaveCommonTypeCtor ac bc | |
HaveCommonTypeCtor a a = () |
class IsHomomorphic a Source #
Require this type to be homomorphic.
Instances
IsHomomorphic (a :: k) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
(TypeError ('Text "Type is not homomorphic: " ':<>: 'ShowType (a b)) :: Constraint) => IsHomomorphic (a b :: k2) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc |
genericTypeDocDependencies :: forall a. (Generic a, GTypeHasDoc (GRep a)) => Proxy a -> [SomeDocDefinitionItem] Source #
Implement typeDocDependencies
via getting all immediate fields
of a datatype.
Produces a custom error message for missing Generic
instances:
>>>
data Foo = Foo ()
>>>
length $ genericTypeDocDependencies $ Proxy @Foo
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo () deriving Generic
>>>
length $ genericTypeDocDependencies $ Proxy @Foo
1
Note: this will not include phantom types, I'm not sure yet how this scenario should be handled (@martoon).
customTypeDocMdReference :: (Text, DType) -> [DType] -> WithinParens -> Markdown Source #
Render a reference to a type which consists of type constructor (you have to provide name of this type constructor and documentation for the whole type) and zero or more type arguments.
customTypeDocMdReference' :: (Text, DType) -> [WithinParens -> Markdown] -> WithinParens -> Markdown Source #
More generic version of customTypeDocMdReference
, it accepts
arguments not as types with doc, but printers for them.
homomorphicTypeDocMdReference :: forall (t :: Type). (Typeable t, TypeHasDoc t, IsHomomorphic t) => Proxy t -> WithinParens -> Markdown Source #
Derive typeDocMdReference
, for homomorphic types only.
poly1TypeDocMdReference :: forall t (r :: Type) (a :: Type). (r ~ t a, Typeable t, Each '[TypeHasDoc] [r, a], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown Source #
Derive typeDocMdReference
, for polymorphic type with one
type argument, like Maybe Integer
.
poly2TypeDocMdReference :: forall t (r :: Type) (a :: Type) (b :: Type). (r ~ t a b, Typeable t, Each '[TypeHasDoc] [r, a, b], IsHomomorphic t) => Proxy r -> WithinParens -> Markdown Source #
Derive typeDocMdReference
, for polymorphic type with two
type arguments, like Lambda Integer Natural
.
homomorphicTypeDocHaskellRep :: forall a. (Generic a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep a Source #
Implement typeDocHaskellRep
for a homomorphic type.
Note that it does not require your type to be of IsHomomorphic
instance,
which can be useful for some polymorphic types which, for documentation
purposes, we want to consider homomorphic.
Example: Operation
is in fact polymorphic, but we don't want this fact to
be reflected in the documentation.
Produces a custom error message for missing Generic
instances:
>>>
data Foo = Foo ()
>>>
isJust $ homomorphicTypeDocHaskellRep (Proxy @Foo) []
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo () deriving Generic
>>>
isJust $ homomorphicTypeDocHaskellRep (Proxy @Foo) []
True
concreteTypeDocHaskellRep :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a), HaveCommonTypeCtor b a) => TypeDocHaskellRep b Source #
Implement typeDocHaskellRep
on example of given concrete type.
This is a best effort attempt to implement typeDocHaskellRep
for polymorphic
types, as soon as there is no simple way to preserve type variables when
automatically deriving Haskell representation of a type.
Produces a custom error message for missing Generic
instances:
>>>
data Foo a = Foo a
>>>
isJust $ concreteTypeDocHaskellRep @(Foo Integer) @(Foo ()) Proxy []
... ... GHC.Generics.Rep (Foo Integer) ... is stuck. Likely ... Generic (Foo Integer) ... instance is missing or out of scope. ...
>>>
data Foo a = Foo a deriving (Generic, IsoValue)
>>>
isJust $ concreteTypeDocHaskellRep @(Foo Integer) @(Foo ()) Proxy []
True
unsafeConcreteTypeDocHaskellRep :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (GRep a)) => TypeDocHaskellRep b Source #
Version of concreteTypeDocHaskellRep
which does not ensure
whether the type for which representation is built is any similar to
the original type which you implement a TypeHasDoc
instance for.
>>>
data Foo = Foo ()
>>>
isJust $ unsafeConcreteTypeDocHaskellRep @Foo @() Proxy []
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo () deriving (Generic, IsoValue)
>>>
isJust $ unsafeConcreteTypeDocHaskellRep @Foo @() Proxy []
True
haskellAddNewtypeField :: Text -> TypeDocHaskellRep a -> TypeDocHaskellRep a Source #
Add field name for newtype
.
Since newtype
field is automatically erased. Use this function
to add the desired field name.
haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a Source #
Erase fields from Haskell datatype representation.
Use this when rendering fields names is undesired.
haskellRepMap :: (Text -> Text) -> TypeDocHaskellRep a -> TypeDocHaskellRep a Source #
Like haskellRepAdjust
, but can't add or remove field names.
haskellRepAdjust :: (Maybe Text -> Maybe Text) -> TypeDocHaskellRep a -> TypeDocHaskellRep a Source #
Adjust field names using a function. Can add or remove field names.
homomorphicTypeDocMichelsonRep :: forall a. KnownIsoT a => TypeDocMichelsonRep a Source #
Implement typeDocMichelsonRep
for homomorphic type.
concreteTypeDocMichelsonRep :: forall a b. (Typeable a, KnownIsoT a, HaveCommonTypeCtor b a) => TypeDocMichelsonRep b Source #
Implement typeDocMichelsonRep
on example of given concrete type.
This function exists for the same reason as concreteTypeDocHaskellRep
.
unsafeConcreteTypeDocMichelsonRep :: forall a b. (Typeable a, KnownIsoT a) => TypeDocMichelsonRep b Source #
Version of unsafeConcreteTypeDocHaskellRep
which does not ensure
whether the type for which representation is built is any similar to
the original type which you implement a TypeHasDoc
instance for.
Doc element with description of a type.
DType :: TypeHasDoc a => Proxy a -> DType |
Instances
Eq DType Source # | |
Ord DType Source # | |
DocItem DType Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc type DocItemPlacement DType :: DocItemPlacementKind Source # type DocItemReferenced DType :: DocItemReferencedKind Source # docItemPos :: Natural Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DType -> DocItemRef (DocItemPlacement DType) (DocItemReferenced DType) Source # docItemToMarkdown :: HeaderLevel -> DType -> Markdown Source # docItemToToc :: HeaderLevel -> DType -> Markdown Source # docItemDependencies :: DType -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DType] -> [DType] Source # | |
Buildable DType Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
type DocItemPlacement DType Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
type DocItemReferenced DType Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc |
newtype DStorageType Source #
Doc element with description of contract storage type.
Instances
dStorage :: forall store. TypeHasDoc store => DStorageType Source #
Shortcut for DStorageType
.
class GTypeHasDoc (x :: Type -> Type) Source #
Generic traversal for automatic deriving of some methods in TypeHasDoc
.
gTypeDocHaskellRep
Instances
GTypeHasDoc (V1 :: Type -> Type) Source # | |
(GTypeHasDoc x, GTypeHasDoc y) => GTypeHasDoc (x :+: y) Source # | |
(GProductHasDoc x, KnownSymbol ctor) => GTypeHasDoc (C1 ('MetaCons ctor _1 _2) x) Source # | |
GTypeHasDoc x => GTypeHasDoc (D1 ('MetaData _a _b _c 'False) x) Source # | |
GTypeHasDoc x => GTypeHasDoc (D1 ('MetaData _a _b _c 'True) x) Source # | |
class GProductHasDoc (x :: Type -> Type) Source #
Product type traversal for TypeHasDoc
.
gProductDocHaskellRep
Instances
GProductHasDoc (U1 :: Type -> Type) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
(GProductHasDoc x, GProductHasDoc y) => GProductHasDoc (x :*: y) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
(TypeHasDoc a, KnownSymbol field) => GProductHasDoc (S1 ('MetaSel ('Just field) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
TypeHasDoc a => GProductHasDoc (S1 ('MetaSel ('Nothing :: Maybe Symbol) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] |
dTypeDep :: forall (t :: Type). TypeHasDoc t => SomeDocDefinitionItem Source #
Create a DType
in form suitable for putting to typeDocDependencies
.
dTypeDepP :: forall (t :: Type). TypeHasDoc t => Proxy t -> SomeDocDefinitionItem Source #
Proxy version of dTypeDep
.
buildADTRep :: forall a. (WithinParens -> a -> Markdown) -> ADTRep a -> Markdown Source #
Show given ADTRep
in a neat way.
applyWithinParens :: WithinParens -> Markdown -> Markdown Source #
buildTypeWithinParens :: forall a. Typeable a => WithinParens -> Markdown Source #
Show type, wrapping into parentheses if necessary.