| 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
- class KnownAnnTag tag where
- type TypeAnn = Annotation TypeTag
- type FieldAnn = Annotation FieldTag
- type VarAnn = Annotation VarTag
- type SomeAnn = Annotation SomeTag
- noAnn :: Annotation a
- ann :: HasCallStack => Text -> Annotation a
- mkAnnotation :: Text -> Either Text (Annotation a)
- specialVarAnns :: [Text]
- specialFieldAnn :: Text
- isValidAnnStart :: Char -> Bool
- isValidAnnBodyChar :: Char -> Bool
- renderAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc
- renderWEAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc
- 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 #
type TypeAnn = Annotation TypeTag Source #
type FieldAnn = Annotation FieldTag Source #
type VarAnn = Annotation VarTag Source #
type SomeAnn = Annotation SomeTag Source #
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
renderAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc Source #
renderWEAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc Source #
Prints empty prefix in case of noAnn.
Such functionality is required in case when instruction has two annotations of the same type, former is empty and the latter is not. So that `PAIR noAnn noAnn noAnn %kek` is printed as `PAIR % %kek`
unifyAnn :: Annotation tag -> Annotation tag -> Maybe (Annotation tag) Source #
ifAnnUnified :: Annotation tag -> Annotation tag -> Bool Source #
convAnn :: Annotation tag1 -> Annotation tag2 Source #