1{-# LANGUAGE CPP #-}
2{-# LANGUAGE RankNTypes #-}
3
4-- | The Name Cache
5module NameCache
6    ( lookupOrigNameCache
7    , extendOrigNameCache
8    , extendNameCache
9    , initNameCache
10    , NameCache(..), OrigNameCache
11    ) where
12
13import GhcPrelude
14
15import Module
16import Name
17import UniqSupply
18import TysWiredIn
19import Util
20import Outputable
21import PrelNames
22
23#include "HsVersions.h"
24
25{-
26
27Note [The Name Cache]
28~~~~~~~~~~~~~~~~~~~~~
29The Name Cache makes sure that, during any invocation of GHC, each
30External Name "M.x" has one, and only one globally-agreed Unique.
31
32* The first time we come across M.x we make up a Unique and record that
33  association in the Name Cache.
34
35* When we come across "M.x" again, we look it up in the Name Cache,
36  and get a hit.
37
38The functions newGlobalBinder, allocateGlobalBinder do the main work.
39When you make an External name, you should probably be calling one
40of them.
41
42
43Note [Built-in syntax and the OrigNameCache]
44~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
45
46Built-in syntax like tuples and unboxed sums are quite ubiquitous. To lower
47their cost we use two tricks,
48
49  a. We specially encode tuple and sum Names in interface files' symbol tables
50     to avoid having to look up their names while loading interface files.
51     Namely these names are encoded as by their Uniques. We know how to get from
52     a Unique back to the Name which it represents via the mapping defined in
53     the SumTupleUniques module. See Note [Symbol table representation of names]
54     in BinIface and for details.
55
56  b. We don't include them in the Orig name cache but instead parse their
57     OccNames (in isBuiltInOcc_maybe) to avoid bloating the name cache with
58     them.
59
60Why is the second measure necessary? Good question; afterall, 1) the parser
61emits built-in syntax directly as Exact RdrNames, and 2) built-in syntax never
62needs to looked-up during interface loading due to (a). It turns out that there
63are two reasons why we might look up an Orig RdrName for built-in syntax,
64
65  * If you use setRdrNameSpace on an Exact RdrName it may be
66    turned into an Orig RdrName.
67
68  * Template Haskell turns a BuiltInSyntax Name into a TH.NameG
69    (DsMeta.globalVar), and parses a NameG into an Orig RdrName
70    (Convert.thRdrName).  So, e.g. $(do { reify '(,); ... }) will
71    go this route (#8954).
72
73-}
74
75-- | Per-module cache of original 'OccName's given 'Name's
76type OrigNameCache   = ModuleEnv (OccEnv Name)
77
78lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name
79lookupOrigNameCache nc mod occ
80  | mod == gHC_TYPES || mod == gHC_PRIM || mod == gHC_TUPLE
81  , Just name <- isBuiltInOcc_maybe occ
82  =     -- See Note [Known-key names], 3(c) in PrelNames
83        -- Special case for tuples; there are too many
84        -- of them to pre-populate the original-name cache
85    Just name
86
87  | otherwise
88  = case lookupModuleEnv nc mod of
89        Nothing      -> Nothing
90        Just occ_env -> lookupOccEnv occ_env occ
91
92extendOrigNameCache :: OrigNameCache -> Name -> OrigNameCache
93extendOrigNameCache nc name
94  = ASSERT2( isExternalName name, ppr name )
95    extendNameCache nc (nameModule name) (nameOccName name) name
96
97extendNameCache :: OrigNameCache -> Module -> OccName -> Name -> OrigNameCache
98extendNameCache nc mod occ name
99  = extendModuleEnvWith combine nc mod (unitOccEnv occ name)
100  where
101    combine _ occ_env = extendOccEnv occ_env occ name
102
103-- | The NameCache makes sure that there is just one Unique assigned for
104-- each original name; i.e. (module-name, occ-name) pair and provides
105-- something of a lookup mechanism for those names.
106data NameCache
107 = NameCache {  nsUniqs :: !UniqSupply,
108                -- ^ Supply of uniques
109                nsNames :: !OrigNameCache
110                -- ^ Ensures that one original name gets one unique
111   }
112
113-- | Return a function to atomically update the name cache.
114initNameCache :: UniqSupply -> [Name] -> NameCache
115initNameCache us names
116  = NameCache { nsUniqs = us,
117                nsNames = initOrigNames names }
118
119initOrigNames :: [Name] -> OrigNameCache
120initOrigNames names = foldl' extendOrigNameCache emptyModuleEnv names
121