Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data Notes t where
- 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 -> Notes t -> Notes ('TSet t)
- 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 -> Notes k -> Notes v -> Notes ('TMap k v)
- NTBigMap :: TypeAnn -> Notes k -> Notes v -> Notes ('TBigMap k v)
- NTInt :: TypeAnn -> Notes 'TInt
- NTNat :: TypeAnn -> Notes 'TNat
- NTString :: TypeAnn -> Notes 'TString
- NTBytes :: TypeAnn -> Notes 'TBytes
- NTMutez :: TypeAnn -> Notes 'TMutez
- NTBool :: TypeAnn -> Notes 'TBool
- NTKeyHash :: TypeAnn -> Notes 'TKeyHash
- NTTimestamp :: TypeAnn -> Notes 'TTimestamp
- NTAddress :: TypeAnn -> Notes 'TAddress
- data AnnConvergeError where
- AnnConvergeError :: forall (tag :: Type). (Buildable (Annotation tag), Show (Annotation tag), Typeable tag) => Annotation tag -> Annotation tag -> AnnConvergeError
- converge :: Notes t -> Notes t -> Either AnnConvergeError (Notes t)
- convergeAnns :: forall (tag :: Type). (Buildable (Annotation tag), Show (Annotation tag), Typeable tag) => Annotation tag -> Annotation tag -> Either AnnConvergeError (Annotation tag)
- insertTypeAnn :: forall (b :: T). TypeAnn -> Notes b -> Notes b
- orAnn :: Annotation t -> Annotation t -> Annotation t
- isStar :: SingI t => Notes t -> Bool
- starNotes :: forall t. SingI t => Notes t
- notesSing :: SingI t => Notes t -> Sing t
- notesT :: SingI t => Notes t -> T
Documentation
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
.
Instances
Eq (Notes t) Source # | |
Show (Notes t) Source # | |
NFData (Notes t) Source # | |
Defined in Michelson.Typed.Annotation | |
Buildable (Notes t) Source # | |
Defined in Michelson.Typed.Annotation | |
RenderDoc (Notes t) Source # | |
Defined in Michelson.Typed.Annotation | |
SingI t => ToExpression (Notes t) Source # | |
Defined in Morley.Micheline.Class toExpression :: Notes t -> Expression Source # |
data AnnConvergeError where Source #
AnnConvergeError :: forall (tag :: Type). (Buildable (Annotation tag), Show (Annotation tag), Typeable tag) => Annotation tag -> Annotation tag -> AnnConvergeError |
Instances
Eq AnnConvergeError Source # | |
Defined in Michelson.Typed.Annotation (==) :: AnnConvergeError -> AnnConvergeError -> Bool # (/=) :: AnnConvergeError -> AnnConvergeError -> Bool # | |
Show AnnConvergeError Source # | |
Defined in Michelson.Typed.Annotation showsPrec :: Int -> AnnConvergeError -> ShowS # show :: AnnConvergeError -> String # showList :: [AnnConvergeError] -> ShowS # | |
NFData AnnConvergeError Source # | |
Defined in Michelson.Typed.Annotation rnf :: AnnConvergeError -> () # | |
Buildable AnnConvergeError Source # | |
Defined in Michelson.Typed.Annotation build :: AnnConvergeError -> Builder # |
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).
insertTypeAnn :: forall (b :: T). TypeAnn -> Notes b -> Notes b Source #
Insert the provided type annotation into the provided notes.
orAnn :: Annotation t -> Annotation t -> Annotation t Source #
starNotes :: forall t. SingI t => Notes t Source #
In memory of NStar
constructor.
Generates notes with no annotations.