| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- data Annotation = Annotation {}
 - type AnnPayload = Serialized
 - data AnnTarget name
- = NamedTarget name
 - | ModuleTarget Module
 
 - type CoreAnnTarget = AnnTarget Name
 - data AnnEnv
 - mkAnnEnv :: [Annotation] -> AnnEnv
 - extendAnnEnvList :: AnnEnv -> [Annotation] -> AnnEnv
 - plusAnnEnv :: AnnEnv -> AnnEnv -> AnnEnv
 - emptyAnnEnv :: AnnEnv
 - findAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> CoreAnnTarget -> [a]
 - findAnnsByTypeRep :: AnnEnv -> CoreAnnTarget -> TypeRep -> [[Word8]]
 - deserializeAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> (ModuleEnv [a], NameEnv [a])
 
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 # | |
Defined in GHC.Types.Annotations Methods ppr :: Annotation -> SDoc Source #  | |
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  | 
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  | 
type CoreAnnTarget = AnnTarget Name Source #
The kind of annotation target found in the middle end of the compiler
AnnEnv for collecting and querying 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.
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).