morley-1.0.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.Haskell.Doc

Description

Documentation of types appearing in contracts.

Synopsis

Documentation

type ADTRep a = NonEmpty (Text, [(Maybe Text, 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.

Outer list layer corresponds to union, and the inner one corresponds to products within constructors. Constructors and fields names are present.

newtype WithinParens Source #

Whether given text should be rendered grouped in parentheses (if they make sense).

Constructors

WithinParens Bool 

class Typeable a => TypeHasDoc a where Source #

Description for a Haskell type appearing in documentation.

Minimal complete definition

typeDocMdDescription

Methods

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 for this, but it produces names including module names which is not do we want).

typeDocName :: (Generic a, KnownSymbol (GenericTypeName a)) => 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 for this, but it produces names including module names which is not do we want).

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, * Maybe ().

Consider using one of the following functions as default implementation; which one to use depends on number of type arguments in your type: * homomorphicTypeDocMdReference * poly1TypeDocMdReference * poly2TypeDocMdReference

If none of them fits your purposes precisely, consider using customTypeDocMdReference.

typeDocMdReference :: (Typeable a, IsHomomorphic a) => Proxy a -> WithinParens -> Markdown Source #

How reference to this type is rendered, in Markdown.

Examples: * Integer, * Maybe ().

Consider using one of the following functions as default implementation; which one to use depends on number of type arguments in your type: * homomorphicTypeDocMdReference * poly1TypeDocMdReference * poly2TypeDocMdReference

If none of them fits your purposes precisely, consider using customTypeDocMdReference.

typeDocDependencies :: Proxy a -> [SomeTypeWithDoc] Source #

All types which this type directly contains.

Used in automatic types discovery.

typeDocDependencies :: (Generic a, GTypeHasDoc (Rep a)) => Proxy a -> [SomeTypeWithDoc] Source #

All types which this type directly contains.

Used in automatic types discovery.

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 polymorhpic types consider using concreteTypeDocHaskellRep as implementation.

Modifier haskellRepNoFields can be used to hide names of fields, beneficial for newtypes.

Another modifier called haskellRepStripFieldPrefix can be used for datatypes to leave only meaningful part of name in every field.

typeDocHaskellRep :: (Generic a, GTypeHasDoc (Rep a), IsHomomorphic a) => TypeDocHaskellRep a Source #

For complex types - their immediate Haskell representation.

For primitive types set this to Nothing.

For homomorphic types use homomorphicTypeDocHaskellRep implementation.

For polymorhpic types consider using concreteTypeDocHaskellRep as implementation.

Modifier haskellRepNoFields can be used to hide names of fields, beneficial for newtypes.

Another modifier called haskellRepStripFieldPrefix can be used for datatypes to leave only meaningful part of name in every field.

typeDocMichelsonRep :: TypeDocMichelsonRep a Source #

Final michelson representation of a type.

For homomorphic types use homomorphicTypeDocMichelsonRep implementation.

For polymorhpic types consider using concreteTypeDocMichelsonRep as implementation.

typeDocMichelsonRep :: (SingI (ToT a), IsHomomorphic a) => TypeDocMichelsonRep a Source #

Final michelson representation of a type.

For homomorphic types use homomorphicTypeDocMichelsonRep implementation.

For polymorhpic types consider using concreteTypeDocMichelsonRep as implementation.

Instances
TypeHasDoc Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc () Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

TypeHasDoc Operation Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (a ': ([] :: [Type])) => TypeHasDoc [a] Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (a ': ([] :: [Type])) => TypeHasDoc (Maybe a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyCTypeHasDocC (a ': ([] :: [Type])) => TypeHasDoc (Set a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (cp ': ([] :: [Type])) => TypeHasDoc (ContractRef cp) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (l ': (r ': ([] :: [Type]))) => TypeHasDoc (Either l r) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (a ': (b ': ([] :: [Type]))) => TypeHasDoc (a, b) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

PolyTypeHasDocC (a ': (b ': (c ': ([] :: [Type])))) => TypeHasDoc (a, b, c) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

Methods

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

typeDocMdDescription :: Markdown Source #

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

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

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

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

type TypeDocHaskellRep a = Proxy a -> Maybe (Maybe DocTypeRepLHS, ADTRep SomeTypeWithDoc) Source #

Signature of typeDocHaskellRep function.

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 polymorhpic 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 polymorhpic 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 polymorhpic type.

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.

Constructors

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

typeDocDependencies' :: TypeHasDoc a => Proxy a -> [SomeDocDefinitionItem] Source #

Like typeDocDependencies but returns values of more common type which is used in docItemDependencies.

class HaveCommonTypeCtor a b Source #

Require two types to be built from the same type constructor.

E.g. HaveCommonTypeCtor (Maybe Integer) (Maybe Natural) is defined, while HaveCmmonTypeCtor (Maybe Integer) [Integer] is not.

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

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

class IsHomomorphic a Source #

Require this type to be homomorphic.

Instances
IsHomomorphic (a :: k) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

Defined in Michelson.Typed.Haskell.Doc

genericTypeDocDependencies :: forall a. (Generic a, GTypeHasDoc (Rep a)) => Proxy a -> [SomeTypeWithDoc] Source #

Implement typeDocDependencies via getting all immediate fields of a datatype.

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.

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 (Rep 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 polymorhpic types which, for documentation purposes, we want to consider homomorphic. Example: Operation is in fact polymorhpic, but we don't want this fact to be reflected in the documentation.

concreteTypeDocHaskellRep :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep 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 polymorhpic types, as soon as there is no simple way to preserve type variables when automatically deriving Haskell representation of a type.

concreteTypeDocHaskellRepUnsafe :: forall a b. (Typeable a, GenericIsoValue a, GTypeHasDoc (Rep 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.

haskellRepNoFields :: TypeDocHaskellRep a -> TypeDocHaskellRep a Source #

Erase fields from Haskell datatype representation.

Use this when rendering fields names is undesired.

haskellRepStripFieldPrefix :: HasCallStack => TypeDocHaskellRep a -> TypeDocHaskellRep a Source #

Cut fields prefixes which we use according to the style guide.

E.g. cmMyField field will be transformed to myField.

homomorphicTypeDocMichelsonRep :: forall a. SingI (ToT a) => TypeDocMichelsonRep a Source #

Implement typeDocMichelsonRep for homomorphic type.

concreteTypeDocMichelsonRep :: forall a b. (Typeable a, SingI (ToT a), HaveCommonTypeCtor b a) => TypeDocMichelsonRep b Source #

Implement typeDocMichelsonRep on example of given concrete type.

This function exists for the same reason as concreteTypeDocHaskellRep.

concreteTypeDocMichelsonRepUnsafe :: forall a b. (Typeable a, SingI (ToT a)) => TypeDocMichelsonRep b Source #

Version of concreteTypeDocHaskellRepUnsafe 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 DType where Source #

Doc element with description of a type.

Constructors

DType :: TypeHasDoc a => Proxy a -> DType 
Instances
Eq DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Doc

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

DocItem DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemPosition DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type DocItemPlacement DType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

class GTypeHasDoc (x :: Type -> Type) Source #

Generic traversal for automatic deriving of some methods in TypeHasDoc.

Minimal complete definition

gTypeDocHaskellRep

Instances
(TypeError (Text "Cannot derive documentation for void-like type") :: Constraint) => GTypeHasDoc (V1 :: Type -> Type) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

(GTypeHasDoc x, GTypeHasDoc y) => GTypeHasDoc (x :+: y) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

GTypeHasDoc x => GTypeHasDoc (D1 i x) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

(GProductHasDoc x, KnownSymbol ctor) => GTypeHasDoc (C1 (MetaCons ctor _1 _2) x) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

buildADTRep :: forall a. (WithinParens -> a -> Markdown) -> ADTRep a -> Markdown Source #

Show given ADTRep in a neat way.