lorentz-0.6.1: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Annotation

Description

Type and field annotations for Lorentz types.

Synopsis

Documentation

data FollowEntrypointFlag Source #

Used in GHasAnnotation and HasAnnotation as a flag to track whether or not it directly follows an entrypoint to avoid introducing extra entrypoints.

data GenerateFieldAnnFlag Source #

Used in GHasAnnotation as a flag to track whether or not field/constructor annotations should be generated.

class HasAnnotation a where Source #

This class defines the type and field annotations for a given type. Right now the type annotations come from names in a named field, and field annotations are generated from the record fields.

Minimal complete definition

Nothing

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT a) Source #

default getAnnotation :: (GHasAnnotation (Rep a), GValueType (Rep a) ~ ToT a) => FollowEntrypointFlag -> Notes (ToT a) Source #

Instances

Instances details
HasAnnotation Bool Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Integer Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Natural Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation () Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation ByteString Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Address Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation EpAddress Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation KeyHash Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation MText Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Mutez Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Operation Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation PublicKey Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Signature Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Timestamp Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Empty Source # 
Instance details

Defined in Lorentz.Empty

HasAnnotation a => HasAnnotation [a] Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT [a]) Source #

HasAnnotation a => HasAnnotation (Maybe a) Source # 
Instance details

Defined in Lorentz.Annotation

KnownIsoT v => HasAnnotation (Set v) Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation a => HasAnnotation (ContractRef a) Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

HasAnnotation (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (UParam entries)) Source #

(HasAnnotation a, HasAnnotation b) => HasAnnotation (a, b) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b)) Source #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (Map k v) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (Map k v)) Source #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (BigMap k v) Source # 
Instance details

Defined in Lorentz.Annotation

(HasAnnotation (ZippedStack i), HasAnnotation (ZippedStack o)) => HasAnnotation (i :-> o) Source # 
Instance details

Defined in Lorentz.Zip

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (i :-> o)) Source #

HasAnnotation (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (MigrationScript oldStore newStore)) Source #

(HasAnnotation a, HasAnnotation b) => HasAnnotation (Void_ a b) Source # 
Instance details

Defined in Lorentz.Macro

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (Void_ a b)) Source #

(HasAnnotation a, HasAnnotation r) => HasAnnotation (View a r) Source # 
Instance details

Defined in Lorentz.Macro

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (View a r)) Source #

HasAnnotation (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

(HasAnnotation a, HasAnnotation b, HasAnnotation c) => HasAnnotation (a, b, c) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b, c)) Source #

(HasAnnotation (Maybe a), KnownSymbol name) => HasAnnotation (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (NamedF Maybe a name)) Source #

(HasAnnotation a, KnownSymbol name) => HasAnnotation (NamedF Identity a name) Source # 
Instance details

Defined in Lorentz.Annotation

(HasAnnotation a, HasAnnotation b, HasAnnotation c, HasAnnotation d) => HasAnnotation (a, b, c, d) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b, c, d)) Source #

(HasAnnotation a, HasAnnotation b, HasAnnotation c, HasAnnotation d, HasAnnotation e) => HasAnnotation (a, b, c, d, e) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b, c, d, e)) Source #

(HasAnnotation a, HasAnnotation b, HasAnnotation c, HasAnnotation d, HasAnnotation e, HasAnnotation f) => HasAnnotation (a, b, c, d, e, f) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b, c, d, e, f)) Source #

(HasAnnotation a, HasAnnotation b, HasAnnotation c, HasAnnotation d, HasAnnotation e, HasAnnotation f, HasAnnotation g) => HasAnnotation (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

getAnnotation :: FollowEntrypointFlag -> Notes (ToT (a, b, c, d, e, f, g)) Source #

class GHasAnnotation a where Source #

A Generic HasAnnotation implementation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType a), FieldAnn) Source #

Instances

Instances details
GHasAnnotation (U1 :: Type -> Type) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType U1), FieldAnn) Source #

HasAnnotation x => GHasAnnotation (Rec0 x) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (Rec0 x)), FieldAnn) Source #

(GHasAnnotation x, GHasAnnotation y) => GHasAnnotation (x :+: y) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (x :+: y)), FieldAnn) Source #

(GHasAnnotation x, GHasAnnotation y) => GHasAnnotation (x :*: y) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (x :*: y)), FieldAnn) Source #

GHasAnnotation x => GHasAnnotation (M1 D i1 x) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (M1 D i1 x)), FieldAnn) Source #

(GHasAnnotation x, KnownSymbol a) => GHasAnnotation (M1 C ('MetaCons a _p _f) x) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (M1 C ('MetaCons a _p _f) x)), FieldAnn) Source #

GHasAnnotation x => GHasAnnotation (M1 S ('MetaSel ('Nothing :: Maybe Symbol) b c d) x) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (M1 S ('MetaSel 'Nothing b c d) x)), FieldAnn) Source #

(GHasAnnotation x, KnownSymbol a) => GHasAnnotation (M1 S ('MetaSel ('Just a) b c d) x) Source # 
Instance details

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (M1 S ('MetaSel ('Just a) b c d) x)), FieldAnn) Source #

gGetAnnotationNoField :: forall a. (GHasAnnotation (Rep a), GValueType (Rep a) ~ ToT a) => FollowEntrypointFlag -> Notes (ToT a) Source #

Use this in the instance of HasAnnotation when field annotations should not be generated.

insertTypeAnn :: forall (b :: T). TypeAnn -> Notes b -> Notes b #