ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Annotations

Description

Support for source code annotation feature of GHC. That is the ANN pragma.

(c) The University of Glasgow 2006 (c) The GRASP/AQUA Project, Glasgow University, 1992-1998

Synopsis

Main Annotation data types

data Annotation Source #

Represents an annotation after it has been sufficiently desugared from it's initial form of AnnDecl

Constructors

Annotation 

Fields

Instances

Instances details
Outputable Annotation Source # 
Instance details

Defined in GHC.Types.Annotations

type AnnPayload Source #

Arguments

 = Serialized

The "payload" of an annotation allows recovery of its value at a given type, and can be persisted to an interface file

data AnnTarget name Source #

An annotation target

Constructors

NamedTarget name

We are annotating something with a name: a type or identifier

ModuleTarget Module

We are annotating a particular module

Instances

Instances details
Functor AnnTarget Source # 
Instance details

Defined in GHC.Types.Annotations

Methods

fmap :: (a -> b) -> AnnTarget a -> AnnTarget b Source #

(<$) :: a -> AnnTarget b -> AnnTarget a Source #

Binary name => Binary (AnnTarget name) Source # 
Instance details

Defined in GHC.Types.Annotations

Methods

put_ :: BinHandle -> AnnTarget name -> IO () Source #

put :: BinHandle -> AnnTarget name -> IO (Bin (AnnTarget name)) Source #

get :: BinHandle -> IO (AnnTarget name) Source #

Outputable name => Outputable (AnnTarget name) Source # 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc Source #

pprPrec :: Rational -> AnnTarget name -> SDoc Source #

type CoreAnnTarget = AnnTarget Name Source #

The kind of annotation target found in the middle end of the compiler

AnnEnv for collecting and querying Annotations

data AnnEnv Source #

A collection of annotations

mkAnnEnv :: [Annotation] -> AnnEnv Source #

Construct a new annotation environment that contains the list of annotations provided.

extendAnnEnvList :: AnnEnv -> [Annotation] -> AnnEnv Source #

Add the given annotation to the environment.

plusAnnEnv :: AnnEnv -> AnnEnv -> AnnEnv Source #

Union two annotation environments.

emptyAnnEnv :: AnnEnv Source #

An empty annotation environment.

findAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> CoreAnnTarget -> [a] Source #

Find the annotations attached to the given target as Typeable values of your choice. If no deserializer is specified, only transient annotations will be returned.

findAnnsByTypeRep :: AnnEnv -> CoreAnnTarget -> TypeRep -> [[Word8]] Source #

Find the annotations attached to the given target as Typeable values of your choice. If no deserializer is specified, only transient annotations will be returned.

deserializeAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> (ModuleEnv [a], NameEnv [a]) Source #

Deserialize all annotations of a given type. This happens lazily, that is no deserialization will take place until the [a] is actually demanded and the [a] can also be empty (the UniqFM is not filtered).