ghc-lib-parser-8.8.1.20191204: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

Annotations

Contents

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
Outputable Annotation Source # 
Instance details

Defined in 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
Functor AnnTarget Source # 
Instance details

Defined in Annotations

Methods

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

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

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

Defined in Annotations

Methods

ppr :: AnnTarget name -> SDoc Source #

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

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

Defined in Annotations

Methods

getUnique :: AnnTarget name -> Unique Source #

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

Defined in Annotations

Methods

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

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

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

type CoreAnnTarget = AnnTarget Name Source #

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

getAnnTargetName_maybe :: AnnTarget name -> Maybe name Source #

Get the name of an annotation target if it exists.

AnnEnv for collecting and querying Annotations

data AnnEnv Source #

A collection of annotations Can't use a type synonym or we hit bug #2412 due to source import

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 -> UniqFM [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).