| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Morley.Michelson.Untyped.Annotation
Description
Michelson annotations in untyped model.
Synopsis
- newtype Annotation tag = UnsafeAnnotation {
- unAnnotation :: Text
- data VarAnns
- pattern Annotation :: Text -> Annotation tag
- pattern WithAnn :: Annotation tag -> Annotation tag
- data AnnotationSet = AnnotationSet {}
- annsCount :: AnnotationSet -> (Int, Int, Int)
- emptyAnnSet :: AnnotationSet
- firstAnn :: KnownAnnTag tag => AnnotationSet -> Annotation tag
- fullAnnSet :: [TypeAnn] -> [FieldAnn] -> [VarAnn] -> AnnotationSet
- isNoAnnSet :: AnnotationSet -> Bool
- minAnnSetSize :: AnnotationSet -> Int
- secondAnn :: KnownAnnTag tag => AnnotationSet -> Annotation tag
- singleAnnSet :: forall tag. KnownAnnTag tag => Annotation tag -> AnnotationSet
- singleGroupAnnSet :: forall tag. KnownAnnTag tag => [Annotation tag] -> AnnotationSet
- minimizeAnnSet :: AnnotationSet -> 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 FieldTag
- data TypeTag
- data FieldTag
- data VarTag
- noAnn :: Annotation a
- annQ :: QuasiQuoter
- varAnnQ :: QuasiQuoter
- fieldAnnQ :: QuasiQuoter
- typeAnnQ :: QuasiQuoter
- mkAnnotation :: Text -> Either Text (Annotation a)
- specialVarAnns :: [Text]
- specialFieldAnn :: Text
- isValidAnnStart :: Char -> Bool
- isValidAnnBodyChar :: Char -> Bool
- orAnn :: Annotation t -> Annotation t -> Annotation t
- unifyAnn :: Annotation tag -> Annotation tag -> Maybe (Annotation tag)
- unifyPairFieldAnn :: FieldAnn -> FieldAnn -> Maybe FieldAnn
- convergeVarAnns :: VarAnn -> VarAnn -> VarAnn
- ifAnnUnified :: Annotation tag -> Annotation tag -> Bool
- 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:
%|%%|%|[:%][_0-9a-zA-Z][_0-9a-zA-Z.%@]*
Constructors
| UnsafeAnnotation | |
Fields
| |
Instances
Either one or two variable annotations
Constructors
| OneVarAnn VarAnn | |
| TwoVarAnns VarAnn VarAnn |
Instances
| Show VarAnns Source # | |
| Generic VarAnns Source # | |
| NFData VarAnns Source # | |
Defined in Morley.Michelson.Untyped.Annotation | |
| type Rep VarAnns Source # | |
Defined in Morley.Michelson.Untyped.Annotation type Rep VarAnns = D1 ('MetaData "VarAnns" "Morley.Michelson.Untyped.Annotation" "morley-1.16.3-inplace" 'False) (C1 ('MetaCons "OneVarAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "TwoVarAnns" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))) | |
pattern Annotation :: Text -> Annotation tag Source #
Unidirectional pattern synonym used to pattern-match on Annotation
without invoking UnsafeAnnotation
pattern WithAnn :: Annotation tag -> Annotation tag Source #
Unidirectional pattern synonym matching only non-empty annotations
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 Annotation, they are omitted
- if one or more noAnn precede a non-empty Annotation, they are kept
- every non-empty Annotation is obviously kept
This is why order for each group is important as well as separation of
different groups of Annotations.
Instances
annsCount :: AnnotationSet -> (Int, Int, Int) Source #
Returns the number of annotations in AnnotationSet for each type.
emptyAnnSet :: AnnotationSet Source #
An AnnotationSet without any Annotation.
firstAnn :: KnownAnnTag tag => AnnotationSet -> Annotation tag Source #
Returns the first annotation in a list of annotations of a specific type
in AnnotationSet, or noAnn if this list is empty.
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.
secondAnn :: KnownAnnTag tag => AnnotationSet -> Annotation tag Source #
Returns the second annotation in a list of annotations of a specific type
in AnnotationSet, or noAnn if this list contains less than 2 elements.
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.
minimizeAnnSet :: AnnotationSet -> AnnotationSet Source #
Removes all unnecessary Annotations. See AnnotationSet.
Rendering
class Typeable (tag :: Type) => KnownAnnTag tag where Source #
A constraint representing that type-level annotation tag is known at compile-time
Methods
What prefix is used for the given annotation type (identified by tag) in Michelson code,
i.e. % for field annotations, @ for variable annotations, : for type annotations
Instances
| KnownAnnTag VarTag Source # | |
Defined in Morley.Michelson.Untyped.Annotation | |
| KnownAnnTag FieldTag Source # | |
Defined in Morley.Michelson.Untyped.Annotation | |
| KnownAnnTag TypeTag Source # | |
Defined in Morley.Michelson.Untyped.Annotation | |
type TypeAnn = Annotation TypeTag Source #
A convenience synonym for type Annotation
type FieldAnn = Annotation FieldTag Source #
A convenience synonym for field Annotation
type VarAnn = Annotation VarTag Source #
A convenience synonym for variable Annotation
type SomeAnn = Annotation SomeTag Source #
A convenience synonym for "some" Annotation, i.e. its type is unknown at compile-time
type RootAnn = Annotation FieldTag Source #
Field annotation for the entire parameter.
Type-level tag for type annotations
Instances
| KnownAnnTag TypeTag Source # | |
Defined in Morley.Michelson.Untyped.Annotation | |
Type-level tag for field annotations
Instances
Type-level tag for variable annotations
Creation and conversions
noAnn :: Annotation a Source #
Empty Annotation, i.e. no annotation
annQ :: QuasiQuoter Source #
>>>:t [annQ||]... :: forall k (tag :: k). Annotation tag
>>>:t [annQ|abc|]... :: forall k (tag :: k). Annotation tag
varAnnQ :: QuasiQuoter Source #
>>>:t [varAnnQ||]... :: VarAnn
>>>:t [varAnnQ|abc|]... :: VarAnn
fieldAnnQ :: QuasiQuoter Source #
>>>:t [fieldAnnQ||]... :: FieldAnn
>>>:t [fieldAnnQ|abc|]... :: FieldAnn
typeAnnQ :: QuasiQuoter Source #
>>>:t [typeAnnQ||]... :: TypeAnn
>>>:t [typeAnnQ|abc|]... :: TypeAnn
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
orAnn :: Annotation t -> Annotation t -> Annotation t Source #
Returns the first annotation if it's not empty, or the second one otherwise.
"a" `orAnn` "b" == "a" "a" `orAnn` "" == "a" "" `orAnn` "b" == "b" "" `orAnn` "" == ""
unifyAnn :: Annotation tag -> Annotation tag -> Maybe (Annotation tag) Source #
Given two type or field annotations, attempt to converge them by joining
these annotations with the following rule:
1. If either annotation is empty, an empty annotation is returned;
2. If both annotations are equal, return this annotation;
3. Otherwise, returns Nothing.
This function is used primarily for type-checking and attempts to imitate the reference implementation's observed behavior with annotations.
unifyPairFieldAnn :: FieldAnn -> FieldAnn -> Maybe FieldAnn Source #
Given two field annotations where one of them is used in CAR or CDR,
attempt to converge them by joining these annotations with the following rule:
1. If either annotation is empty, return the non-empty one (or empty if both are empty);
2. If both annotations are equal, return this annotation;
3. Otherwise, returns Nothing.
This function is used primarily for type-checking and attempts to imitate the reference implementation's observed behavior with field annotations when CAR and CDR are used with pairs.
convergeVarAnns :: VarAnn -> VarAnn -> VarAnn Source #
Keeps an annotation if and only if the two of them are equal and returns an empty annotation otherwise.
ifAnnUnified :: Annotation tag -> Annotation tag -> Bool Source #
convAnn :: Annotation tag1 -> Annotation tag2 Source #
Convert annotation from one type to another