| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Michelson.Untyped.Annotation
Description
Michelson annotations in untyped model.
Synopsis
- newtype Annotation tag = AnnotationUnsafe {
- unAnnotation :: Text
- pattern Annotation :: Text -> Annotation tag
- pattern WithAnn :: Annotation tag -> Annotation tag
- data AnnotationSet
- emptyAnnSet :: AnnotationSet
- fullAnnSet :: [TypeAnn] -> [FieldAnn] -> [VarAnn] -> AnnotationSet
- isNoAnnSet :: AnnotationSet -> Bool
- minAnnSetSize :: AnnotationSet -> Int
- singleAnnSet :: forall tag. KnownAnnTag tag => Annotation tag -> AnnotationSet
- singleGroupAnnSet :: forall tag. KnownAnnTag tag => [Annotation tag] -> AnnotationSet
- class Typeable (tag :: Type) => KnownAnnTag tag where
- type TypeAnn = Annotation TypeTag
- type FieldAnn = Annotation FieldTag
- type VarAnn = Annotation VarTag
- type SomeAnn = Annotation SomeTag
- type RootAnn = Annotation RootTag
- noAnn :: Annotation a
- ann :: HasCallStack => Text -> Annotation a
- mkAnnotation :: Text -> Either Text (Annotation a)
- specialVarAnns :: [Text]
- specialFieldAnn :: Text
- isValidAnnStart :: Char -> Bool
- isValidAnnBodyChar :: Char -> Bool
- unifyAnn :: Annotation tag -> Annotation tag -> Maybe (Annotation tag)
- ifAnnUnified :: Annotation tag -> Annotation tag -> Bool
- disjoinVn :: VarAnn -> (VarAnn, VarAnn)
- convAnn :: Annotation tag1 -> Annotation tag2
Documentation
newtype Annotation tag Source #
Generic TypeFieldVariable Annotation
As per Michelson documentation, this type has an invariant:
(except for the first character, here parametrized in the type tag) the
allowed character set is the one matching the following regexp:
%|%%|%|[:%][_a-zA-Z][_0-9a-zA-Z.%@]*
Constructors
| AnnotationUnsafe | |
Fields
| |
Instances
pattern Annotation :: Text -> Annotation tag Source #
pattern WithAnn :: Annotation tag -> Annotation tag Source #
Annotation Set
data AnnotationSet Source #
An AnnotationSet contains all the typefieldvariable Annotations
, with each group in order, associated with an entity.
Note that in its rendering/show instances the unnecessary annotations will be
omitted, as well as in some of the functions operating with it.
Necessary Annotations are the ones strictly required for a consistent
representation.
In particular, for each group (tfv):
- if all annotations are noAnn they are all omitted
- if one or more noAnn follow a non-empty ann, they are omitted
- if one or more noAnn precede a non-empty ann, they are kept
- every non-empty ann is obviously kept
This is why order for each group is important as well as separation of
different groups of Annotations.
Instances
emptyAnnSet :: AnnotationSet Source #
An AnnotationSet without any Annotation.
fullAnnSet :: [TypeAnn] -> [FieldAnn] -> [VarAnn] -> AnnotationSet Source #
An AnnotationSet built from all 3 kinds of Annotation.
isNoAnnSet :: AnnotationSet -> Bool Source #
Returns True if all Annotations in the Set are unnecessaryemptynoAnn.
False otherwise.
minAnnSetSize :: AnnotationSet -> Int Source #
Returns the amount of Annotations that are necessary for a consistent
representation. See AnnotationSet.
singleAnnSet :: forall tag. KnownAnnTag tag => Annotation tag -> AnnotationSet Source #
An AnnotationSet with only a single Annotation (of any kind).
singleGroupAnnSet :: forall tag. KnownAnnTag tag => [Annotation tag] -> AnnotationSet Source #
An AnnotationSet with several Annotations of the same kind.
Rendering
type TypeAnn = Annotation TypeTag Source #
type FieldAnn = Annotation FieldTag Source #
type VarAnn = Annotation VarTag Source #
type SomeAnn = Annotation SomeTag Source #
type RootAnn = Annotation RootTag Source #
Root annotation was added in the Babylon, it looks the same as
field annotation, but has slightly different semantic and can be used
only in parameter ParameterType.
Creation and conversions
noAnn :: Annotation a Source #
ann :: HasCallStack => Text -> Annotation a Source #
Makes an Annotation from its textual value, prefix (%@:) excluded
Throws an error if the given Text contains invalid characters
mkAnnotation :: Text -> Either Text (Annotation a) Source #
Makes an Annotation from its textual value, prefix (%@:) excluded
Returns a Text error message if the given Text contains invalid characters
specialVarAnns :: [Text] Source #
List of all the special Variable Annotations, only allowed in CAR and CDR
instructions, prefix (@) excluded.
These do not respect the rules of isValidAnnStart and isValidAnnBodyChar.
specialFieldAnn :: Text Source #
The only special Field Annotation, only allowed in PAIR, LEFT and
RIGHT instructions, prefix (%) excluded.
This does not respect the rules of isValidAnnStart and isValidAnnBodyChar.
isValidAnnStart :: Char -> Bool Source #
Checks if a Char is valid to be the first of an annotation, prefix
(%@:) excluded, the ones following should be checked with
isValidAnnBodyChar instead.
Note that this does not check Special Annotations, see specialVarAnns
and specialFieldAnn
isValidAnnBodyChar :: Char -> Bool Source #
Checks if a Char is valid to be part of an annotation, following a valid
first character (see isValidAnnStart) and the prefix (%@:).
Note that this does not check Special Annotations, see specialVarAnns
and specialFieldAnn
unifyAnn :: Annotation tag -> Annotation tag -> Maybe (Annotation tag) Source #
ifAnnUnified :: Annotation tag -> Annotation tag -> Bool Source #
convAnn :: Annotation tag1 -> Annotation tag2 Source #