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

Lorentz.Annotation

Description

Type and field annotations for Lorentz types.

Synopsis

Documentation

data AnnOptions Source #

Allow customization of field annotation generated for a type when declaring its HasAnnotation instance.

Constructors

AnnOptions 

Fields

dropPrefixThen :: (Text -> Text) -> Text -> Text Source #

Drops the field name prefix from a field. We assume a convention of the prefix always being lower case, and the first letter of the actual field name being uppercase. It also accepts another function which will be applied directly after dropping the prefix.

appendTo :: Text -> [Text] -> Text -> Text Source #

appendTo suffix fields field appends the given suffix to field if the field exists in the fields list.

toCamel :: Text -> Text #

O(n) Convert casing to camelCasedPhrase. Subject to fusion.

toPascal :: Text -> Text #

O(n) Convert casing to PascalCasePhrase. Subject to fusion.

toSnake :: Text -> Text #

O(n) Convert casing to snake_cased_phrase. Subject to fusion.

ctorNameToAnnWithOptions :: forall ctor. (KnownSymbol ctor, HasCallStack) => AnnOptions -> FieldAnn Source #

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 #

annOptions :: AnnOptions 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 MText Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Operation Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation EpAddress Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Address Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation ChainId Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation KeyHash Source # 
Instance details

Defined in Lorentz.Annotation

HasAnnotation Mutez 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 Never Source # 
Instance details

Defined in Lorentz.Value

HasAnnotation Empty Source # 
Instance details

Defined in Lorentz.Empty

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

Defined in Lorentz.Annotation

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 (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

HasAnnotation (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

HasAnnotation (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

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

Defined in Lorentz.Annotation

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

Defined in Lorentz.Annotation

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

Defined in Lorentz.Annotation

(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

HasAnnotation (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

HasAnnotation (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

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

Defined in Lorentz.Macro

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

Defined in Lorentz.Macro

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

Defined in Lorentz.Annotation

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

Defined in Lorentz.Annotation

(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

(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 #

annOptions :: AnnOptions 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 #

annOptions :: AnnOptions 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 #

annOptions :: AnnOptions Source #

class GHasAnnotation a where Source #

A Generic HasAnnotation implementation

Methods

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

Instances

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

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

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

Defined in Lorentz.Annotation

Methods

gGetAnnotation :: AnnOptions -> FollowEntrypointFlag -> GenerateFieldAnnFlag -> (Notes (GValueType (M1 S ('MetaSel ('Just a) b c d) x)), FieldAnn, VarAnn) 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 #