morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Untyped.Annotation

Description

Michelson annotations in untyped model.

Synopsis

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

Instances details
Monoid VarAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Semigroup VarAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Lift (Annotation tag :: Type) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

lift :: Quote m => Annotation tag -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Annotation tag -> Code m (Annotation tag) #

Functor (Annotation :: Type -> Type) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

fmap :: (a -> b) -> Annotation a -> Annotation b #

(<$) :: a -> Annotation b -> Annotation a #

(Typeable tag, Default (Anns xs)) => Default (Anns (Annotation tag ': xs)) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns (Annotation tag ': xs) #

FromJSON (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

ToJSON (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

(Typeable tag, Typeable k) => Data (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation tag -> c (Annotation tag) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Annotation tag) #

toConstr :: Annotation tag -> Constr #

dataTypeOf :: Annotation tag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Annotation tag)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Annotation tag)) #

gmapT :: (forall b. Data b => b -> b) -> Annotation tag -> Annotation tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation tag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Annotation tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation tag -> m (Annotation tag) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation tag -> m (Annotation tag) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation tag -> m (Annotation tag) #

Generic (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Associated Types

type Rep (Annotation tag) :: Type -> Type #

Methods

from :: Annotation tag -> Rep (Annotation tag) x #

to :: Rep (Annotation tag) x -> Annotation tag #

Typeable tag => Show (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> Annotation tag -> ShowS #

show :: Annotation tag -> String #

showList :: [Annotation tag] -> ShowS #

Default (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

NFData (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

rnf :: Annotation tag -> () #

Eq (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

(==) :: Annotation tag -> Annotation tag -> Bool #

(/=) :: Annotation tag -> Annotation tag -> Bool #

KnownAnnTag tag => RenderDoc (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

AnnotateInstr xs r => AnnotateInstr (Annotation tag ': xs) r Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

annotateInstr :: Anns (Annotation tag ': xs) -> AnnotateInstrArg (Annotation tag ': xs) r -> r Source #

type Rep (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

type Rep (Annotation tag) = D1 ('MetaData "Annotation" "Morley.Michelson.Untyped.Annotation" "morley-1.20.0-inplace" 'True) (C1 ('MetaCons "UnsafeAnnotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data VarAnns Source #

Either one or two variable annotations

Instances

Instances details
Generic VarAnns Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Associated Types

type Rep VarAnns :: Type -> Type #

Methods

from :: VarAnns -> Rep VarAnns x #

to :: Rep VarAnns x -> VarAnns #

Show VarAnns Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

NFData VarAnns Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

rnf :: VarAnns -> () #

type Rep VarAnns Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

pattern Annotation :: Text -> Annotation tag Source #

Unidirectional pattern synonym used to pattern-match on Annotation without invoking UnsafeAnnotation

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.

Constructors

AnnotationSet 

Fields

annsCount :: AnnotationSet -> (Int, Int, Int) Source #

Returns the number of annotations in AnnotationSet for each type.

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.

Rendering

class Typeable (tag :: Type) => KnownAnnTag tag where Source #

A constraint representing that type-level annotation tag is known at compile-time

Methods

annPrefix :: Text Source #

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

Instances details
KnownAnnTag FieldTag Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

KnownAnnTag TypeTag Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

KnownAnnTag VarTag Source # 
Instance details

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 RootAnn = Annotation FieldTag Source #

Field annotation for the entire parameter.

data TypeTag Source #

Type-level tag for type annotations

Instances

Instances details
KnownAnnTag TypeTag Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

data FieldTag Source #

Type-level tag for field annotations

Instances

Instances details
KnownAnnTag FieldTag Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

data VarTag Source #

Type-level tag for variable annotations

Instances

Instances details
Monoid VarAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Semigroup VarAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

KnownAnnTag VarTag Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

data AnyAnn Source #

Datatype representing arbitrary annotation.

Instances

Instances details
FromJSON AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

ToJSON AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Data AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnyAnn -> c AnyAnn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnyAnn #

toConstr :: AnyAnn -> Constr #

dataTypeOf :: AnyAnn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnyAnn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnyAnn) #

gmapT :: (forall b. Data b => b -> b) -> AnyAnn -> AnyAnn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnyAnn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnyAnn -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnyAnn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnyAnn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnyAnn -> m AnyAnn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnyAnn -> m AnyAnn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnyAnn -> m AnyAnn #

Generic AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Associated Types

type Rep AnyAnn :: Type -> Type #

Methods

from :: AnyAnn -> Rep AnyAnn x #

to :: Rep AnyAnn x -> AnyAnn #

Show AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

NFData AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

rnf :: AnyAnn -> () #

Eq AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

(==) :: AnyAnn -> AnyAnn -> Bool #

(/=) :: AnyAnn -> AnyAnn -> Bool #

RenderDoc AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

type Rep AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

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