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

Morley.Michelson.Typed.Annotation

Contents

Description

Module, providing Notes t data type, which holds annotations for a given type t.

Annotation type Notes t is a tree, each leaf is either a star (*) or a constructor holding some annotation data for a given type t. Star corresponds to the case when given Michelson type contains no annotations.

This module also provides some utility functions which are used to combine two annotations trees a and b into a new one c in such a way that c can be obtained from both a and b by replacing some * leaves with type or/and field annotations.

Synopsis

Documentation

data Notes t where Source #

Data type, holding annotation data for a given Michelson type t.

Each constructor corresponds to exactly one constructor of T and holds all type and field annotations that can be attributed to a Michelson type corresponding to t.

Constructors

NTKey :: TypeAnn -> Notes 'TKey 
NTUnit :: TypeAnn -> Notes 'TUnit 
NTSignature :: TypeAnn -> Notes 'TSignature 
NTChainId :: TypeAnn -> Notes 'TChainId 
NTOption :: TypeAnn -> Notes t -> Notes ('TOption t) 
NTList :: TypeAnn -> Notes t -> Notes ('TList t) 
NTSet :: TypeAnn -> Notes t -> Notes ('TSet t) 
NTOperation :: TypeAnn -> Notes 'TOperation 
NTContract :: TypeAnn -> Notes t -> Notes ('TContract t) 
NTTicket :: TypeAnn -> Notes t -> Notes ('TTicket t) 
NTPair :: TypeAnn -> FieldAnn -> FieldAnn -> VarAnn -> VarAnn -> Notes p -> Notes q -> Notes ('TPair p q) 
NTOr :: TypeAnn -> FieldAnn -> FieldAnn -> Notes p -> Notes q -> Notes ('TOr p q) 
NTLambda :: TypeAnn -> Notes p -> Notes q -> Notes ('TLambda p q) 
NTMap :: TypeAnn -> Notes k -> Notes v -> Notes ('TMap k v) 
NTBigMap :: TypeAnn -> Notes k -> Notes v -> Notes ('TBigMap k v) 
NTInt :: TypeAnn -> Notes 'TInt 
NTNat :: TypeAnn -> Notes 'TNat 
NTString :: TypeAnn -> Notes 'TString 
NTBytes :: TypeAnn -> Notes 'TBytes 
NTMutez :: TypeAnn -> Notes 'TMutez 
NTBool :: TypeAnn -> Notes 'TBool 
NTKeyHash :: TypeAnn -> Notes 'TKeyHash 
NTBls12381Fr :: TypeAnn -> Notes 'TBls12381Fr 
NTBls12381G1 :: TypeAnn -> Notes 'TBls12381G1 
NTBls12381G2 :: TypeAnn -> Notes 'TBls12381G2 
NTTimestamp :: TypeAnn -> Notes 'TTimestamp 
NTAddress :: TypeAnn -> Notes 'TAddress 
NTChest :: TypeAnn -> Notes 'TChest 
NTChestKey :: TypeAnn -> Notes 'TChestKey 
NTNever :: TypeAnn -> Notes 'TNever 
NTTxRollupL2Address :: TypeAnn -> Notes 'TTxRollupL2Address 
NTSaplingState :: forall (n :: Peano). TypeAnn -> Sing n -> Notes ('TSaplingState n) 
NTSaplingTransaction :: forall (n :: Peano). TypeAnn -> Sing n -> Notes ('TSaplingTransaction n) 

Instances

Instances details
Lift (Notes t :: Type) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

lift :: Quote m => Notes t -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Notes t -> Code m (Notes t) #

Show (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

showsPrec :: Int -> Notes t -> ShowS #

show :: Notes t -> String #

showList :: [Notes t] -> ShowS #

(SingI t, Default (Anns xs)) => Default (Anns (Notes t ': xs)) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns (Notes t ': xs) #

NFData (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

rnf :: Notes t -> () #

Buildable (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

build :: Notes t -> Builder #

Eq (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

(==) :: Notes t -> Notes t -> Bool #

(/=) :: Notes t -> Notes t -> Bool #

ToExpression (Notes t) Source # 
Instance details

Defined in Morley.Micheline.Class

RenderDoc (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

AnnotateInstr xs r => AnnotateInstr (Notes t ': xs) r Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

annotateInstr :: Anns (Notes t ': xs) -> AnnotateInstrArg (Notes t ': xs) r -> r Source #

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

Insert the provided type annotation into the provided notes.

isStar :: SingI t => Notes t -> Bool Source #

Checks if no annotations are present.

starNotes :: forall t. SingI t => Notes t Source #

In memory of NStar constructor. Generates notes with no annotations.

mkUType :: Notes x -> Ty Source #

Get the term-level type of notes, preserving annotations.

notesSing :: Notes t -> Sing t Source #

Forget information about annotations, pick singleton with the same type.

notesT :: Notes t -> T Source #

Get term-level type of notes.

Helpers

type AnnVar = Anns '[VarAnn] Source #

Anns only containing a single VarAnn.

data Anns xs where Source #

A typed heterogenous list of annotations. Simplified pattern synonyms for common use cases are provided.

Constructors

AnnsCons :: Typeable tag => !(Annotation tag) -> Anns xs -> Anns (Annotation tag ': xs) infixr 5 
AnnsTyCons :: SingI t => !(Notes t) -> Anns xs -> Anns (Notes t ': xs) infixr 5 
AnnsNil :: Anns '[] 

Bundled Patterns

pattern Anns1 :: Typeable a => Annotation a -> Anns '[Annotation a]

Convenience pattern synonym matching a single simple annotation.

pattern Anns2 :: Each '[Typeable] '[a, b] => Annotation a -> Annotation b -> Anns '[Annotation a, Annotation b]

Convenience pattern synonym matching two simple annotations.

pattern Anns2' :: (Typeable a, SingI t) => Annotation a -> Notes t -> Anns '[Annotation a, Notes t]

Convenience pattern synonym matching two annotations, first being a simple one, the second being Notes, corresponding to an annotated type.

pattern Anns3 :: Each '[Typeable] '[a, b, c] => Annotation a -> Annotation b -> Annotation c -> Anns '[Annotation a, Annotation b, Annotation c]

Convenience pattern synonym matching three simple annotations.

pattern Anns3' :: (Each '[Typeable] '[a, b], SingI t) => Annotation a -> Annotation b -> Notes t -> Anns '[Annotation a, Annotation b, Notes t]

Convenience pattern synonym matching three annotations, first two being simple, the last one being Notes, corresponding to an annotated type.

pattern Anns3'' :: (Typeable a, SingI t, SingI u) => Annotation a -> Notes t -> Notes u -> Anns '[Annotation a, Notes t, Notes u]

Convenience pattern synonym matching three annotations, first being a simple one, the last two being Notes, corresponding to annotated types.

pattern Anns4 :: Each '[Typeable] '[a, b, c, d] => Annotation a -> Annotation b -> Annotation c -> Annotation d -> Anns '[Annotation a, Annotation b, Annotation c, Annotation d]

Convenience pattern synonym matching four simple annotations.

pattern Anns4'' :: (Each '[Typeable] '[a, b], SingI t, SingI u) => Annotation a -> Annotation b -> Notes t -> Notes u -> Anns '[Annotation a, Annotation b, Notes t, Notes u]

Convenience pattern synonym matching four annotations, first two being simple, the last two being Notes, corresponding to annotated types.

pattern Anns5' :: (Each '[Typeable] '[a, b, c, d], SingI t) => Annotation a -> Annotation b -> Annotation c -> Annotation d -> Notes t -> Anns '[Annotation a, Annotation b, Annotation c, Annotation d, Notes t]

Convenience pattern synonym matching five annotations, first four being simple, the last one being Notes, corresponding to an annotated type.

Instances

Instances details
Each '[Show] rs => Show (Anns rs) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

showsPrec :: Int -> Anns rs -> ShowS #

show :: Anns rs -> String #

showList :: [Anns rs] -> ShowS #

(SingI t, Default (Anns xs)) => Default (Anns (Notes t ': xs)) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns (Notes t ': xs) #

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

Default (Anns ('[] :: [Type])) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns '[] #

NFData (Anns xs) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

rnf :: Anns xs -> () #

(Eq r, Eq (Anns rs)) => Eq (Anns (r ': rs)) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

(==) :: Anns (r ': rs) -> Anns (r ': rs) -> Bool #

(/=) :: Anns (r ': rs) -> Anns (r ': rs) -> Bool #

Eq (Anns ('[] :: [Type])) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

(==) :: Anns '[] -> Anns '[] -> Bool #

(/=) :: Anns '[] -> Anns '[] -> Bool #

class AnnotateInstr (xs :: [Type]) r where Source #

Utility typeclass to simplify extracting annotations from Anns and passing those as arguments to an untyped instruction data constructor.

Methods

annotateInstr :: Anns xs -> AnnotateInstrArg xs r -> r Source #

Instances

Instances details
AnnotateInstr ('[] :: [Type]) r Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

annotateInstr :: Anns '[] -> AnnotateInstrArg '[] r -> r Source #

AnnotateInstr xs r => AnnotateInstr (Notes t ': xs) r Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

annotateInstr :: Anns (Notes t ': xs) -> AnnotateInstrArg (Notes t ': xs) r -> r Source #

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 #