/compiler/GHC/Types/Annotations.hs

https://github.com/bgamari/ghc · Haskell · 140 lines · 85 code · 23 blank · 32 comment · 4 complexity · 565ed87338111cc3f41d539da7599191 MD5 · raw file

  1. -- |
  2. -- Support for source code annotation feature of GHC. That is the ANN pragma.
  3. --
  4. -- (c) The University of Glasgow 2006
  5. -- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
  6. --
  7. {-# LANGUAGE DeriveFunctor #-}
  8. module GHC.Types.Annotations (
  9. -- * Main Annotation data types
  10. Annotation(..), AnnPayload,
  11. AnnTarget(..), CoreAnnTarget,
  12. -- * AnnEnv for collecting and querying Annotations
  13. AnnEnv,
  14. mkAnnEnv, extendAnnEnvList, plusAnnEnv, emptyAnnEnv,
  15. findAnns, findAnnsByTypeRep,
  16. deserializeAnns
  17. ) where
  18. import GHC.Prelude
  19. import GHC.Utils.Binary
  20. import GHC.Unit.Module ( Module )
  21. import GHC.Unit.Module.Env
  22. import GHC.Types.Name.Env
  23. import GHC.Types.Name
  24. import GHC.Utils.Outputable
  25. import GHC.Serialized
  26. import Control.Monad
  27. import Data.Maybe
  28. import Data.Typeable
  29. import Data.Word ( Word8 )
  30. -- | Represents an annotation after it has been sufficiently desugared from
  31. -- it's initial form of 'GHC.Hs.Decls.AnnDecl'
  32. data Annotation = Annotation {
  33. ann_target :: CoreAnnTarget, -- ^ The target of the annotation
  34. ann_value :: AnnPayload
  35. }
  36. type AnnPayload = Serialized -- ^ The "payload" of an annotation
  37. -- allows recovery of its value at a given type,
  38. -- and can be persisted to an interface file
  39. -- | An annotation target
  40. data AnnTarget name
  41. = NamedTarget name -- ^ We are annotating something with a name:
  42. -- a type or identifier
  43. | ModuleTarget Module -- ^ We are annotating a particular module
  44. deriving (Functor)
  45. -- | The kind of annotation target found in the middle end of the compiler
  46. type CoreAnnTarget = AnnTarget Name
  47. instance Outputable name => Outputable (AnnTarget name) where
  48. ppr (NamedTarget nm) = text "Named target" <+> ppr nm
  49. ppr (ModuleTarget mod) = text "Module target" <+> ppr mod
  50. instance Binary name => Binary (AnnTarget name) where
  51. put_ bh (NamedTarget a) = do
  52. putByte bh 0
  53. put_ bh a
  54. put_ bh (ModuleTarget a) = do
  55. putByte bh 1
  56. put_ bh a
  57. get bh = do
  58. h <- getByte bh
  59. case h of
  60. 0 -> liftM NamedTarget $ get bh
  61. _ -> liftM ModuleTarget $ get bh
  62. instance Outputable Annotation where
  63. ppr ann = ppr (ann_target ann)
  64. -- | A collection of annotations
  65. data AnnEnv = MkAnnEnv { ann_mod_env :: !(ModuleEnv [AnnPayload])
  66. , ann_name_env :: !(NameEnv [AnnPayload])
  67. }
  68. -- | An empty annotation environment.
  69. emptyAnnEnv :: AnnEnv
  70. emptyAnnEnv = MkAnnEnv emptyModuleEnv emptyNameEnv
  71. -- | Construct a new annotation environment that contains the list of
  72. -- annotations provided.
  73. mkAnnEnv :: [Annotation] -> AnnEnv
  74. mkAnnEnv = extendAnnEnvList emptyAnnEnv
  75. -- | Add the given annotation to the environment.
  76. extendAnnEnvList :: AnnEnv -> [Annotation] -> AnnEnv
  77. extendAnnEnvList env =
  78. foldl' extendAnnEnv env
  79. extendAnnEnv :: AnnEnv -> Annotation -> AnnEnv
  80. extendAnnEnv (MkAnnEnv mod_env name_env) (Annotation tgt payload) =
  81. case tgt of
  82. NamedTarget name -> MkAnnEnv mod_env (extendNameEnv_C (++) name_env name [payload])
  83. ModuleTarget mod -> MkAnnEnv (extendModuleEnvWith (++) mod_env mod [payload]) name_env
  84. -- | Union two annotation environments.
  85. plusAnnEnv :: AnnEnv -> AnnEnv -> AnnEnv
  86. plusAnnEnv a b =
  87. MkAnnEnv { ann_mod_env = plusModuleEnv_C (++) (ann_mod_env a) (ann_mod_env b)
  88. , ann_name_env = plusNameEnv_C (++) (ann_name_env a) (ann_name_env b)
  89. }
  90. -- | Find the annotations attached to the given target as 'Typeable'
  91. -- values of your choice. If no deserializer is specified,
  92. -- only transient annotations will be returned.
  93. findAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> CoreAnnTarget -> [a]
  94. findAnns deserialize env
  95. = mapMaybe (fromSerialized deserialize) . findAnnPayloads env
  96. -- | Find the annotations attached to the given target as 'Typeable'
  97. -- values of your choice. If no deserializer is specified,
  98. -- only transient annotations will be returned.
  99. findAnnsByTypeRep :: AnnEnv -> CoreAnnTarget -> TypeRep -> [[Word8]]
  100. findAnnsByTypeRep env target tyrep
  101. = [ ws | Serialized tyrep' ws <- findAnnPayloads env target
  102. , tyrep' == tyrep ]
  103. -- | Find payloads for the given 'CoreAnnTarget' in an 'AnnEnv'.
  104. findAnnPayloads :: AnnEnv -> CoreAnnTarget -> [AnnPayload]
  105. findAnnPayloads env target =
  106. case target of
  107. ModuleTarget mod -> lookupWithDefaultModuleEnv (ann_mod_env env) [] mod
  108. NamedTarget name -> fromMaybe [] $ lookupNameEnv (ann_name_env env) name
  109. -- | Deserialize all annotations of a given type. This happens lazily, that is
  110. -- no deserialization will take place until the [a] is actually demanded and
  111. -- the [a] can also be empty (the UniqFM is not filtered).
  112. deserializeAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> (ModuleEnv [a], NameEnv [a])
  113. deserializeAnns deserialize env
  114. = ( mapModuleEnv deserAnns (ann_mod_env env)
  115. , mapNameEnv deserAnns (ann_name_env env)
  116. )
  117. where deserAnns = mapMaybe (fromSerialized deserialize)