morley-1.0.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.Annotation

Description

Module, providing Notes t data type, which holds annotations for a given type t.

Annotation type Notes t is a tree, each leaf is either a star (*) or a constructor holding some annotation data for a given type t. Star corresponds to the case when given Michelson type contains no annotations.

This module also provides type class Converge along with some utility functions which are used to combine two annotations trees a and b into a new one c in such a way that c can be obtained from both a and b by replacing some * leafs with type or/and field annotations.

Synopsis

Documentation

data Notes t where Source #

Data type, holding annotation data for a given Michelson type t.

Each constructor corresponds to exactly one constructor of T and holds all type and field annotations that can be attributed to a Michelson type corrspoding to t.

Constructors

NTc :: TypeAnn -> Notes (Tc ct) 
NTKey :: TypeAnn -> Notes TKey 
NTUnit :: TypeAnn -> Notes TUnit 
NTSignature :: TypeAnn -> Notes TSignature 
NTChainId :: TypeAnn -> Notes TChainId 
NTOption :: TypeAnn -> Notes t -> Notes (TOption t) 
NTList :: TypeAnn -> Notes t -> Notes (TList t) 
NTSet :: TypeAnn -> TypeAnn -> Notes (TSet ct) 
NTOperation :: TypeAnn -> Notes TOperation 
NTContract :: TypeAnn -> Notes t -> Notes (TContract t) 
NTPair :: TypeAnn -> FieldAnn -> FieldAnn -> Notes p -> Notes q -> Notes (TPair p q) 
NTOr :: TypeAnn -> FieldAnn -> FieldAnn -> Notes p -> Notes q -> Notes (TOr p q) 
NTLambda :: TypeAnn -> Notes p -> Notes q -> Notes (TLambda p q) 
NTMap :: TypeAnn -> TypeAnn -> Notes v -> Notes (TMap k v) 
NTBigMap :: TypeAnn -> TypeAnn -> Notes v -> Notes (TBigMap k v) 
Instances
Eq (Notes t) Source # 
Instance details

Defined in Michelson.Typed.Annotation

Methods

(==) :: Notes t -> Notes t -> Bool #

(/=) :: Notes t -> Notes t -> Bool #

Show (Notes t) Source # 
Instance details

Defined in Michelson.Typed.Annotation

Methods

showsPrec :: Int -> Notes t -> ShowS #

show :: Notes t -> String #

showList :: [Notes t] -> ShowS #

converge :: Notes t -> Notes t -> Either AnnConvergeError (Notes t) Source #

Combines two annotations trees a and b into a new one c in such a way that c can be obtained from both a and b by replacing some empty leaves with type or/and field annotations.

convergeAnns :: forall (tag :: Type). (Buildable (Annotation tag), Show (Annotation tag), Typeable tag) => Annotation tag -> Annotation tag -> Either AnnConvergeError (Annotation tag) Source #

Converge two type or field notes (which may be wildcards).

isStar :: SingI t => Notes t -> Bool Source #

Checks if no annotations are present.

starNotes :: forall t. SingI t => Notes t Source #

In memory of NStar constructor. Generates notes with no annotations.