[project @ 2001-03-05 12:46:16 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Name.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Name]{@Name@: to transmit name info from renamer to typechecker}
5
6 \begin{code}
7 module Name (
8         -- Re-export the OccName stuff
9         module OccName,
10
11         -- The Name type
12         Name,                                   -- Abstract
13         mkLocalName, mkSysLocalName, mkCCallName,
14         mkIPName,
15         mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
16
17         nameUnique, setNameUnique,
18         nameOccName, nameModule, nameModule_maybe,
19         setNameOcc, nameRdrName, setNameModuleAndLoc, 
20         toRdrName, hashName, 
21         globaliseName, localiseName,
22
23         nameSrcLoc, 
24
25         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
26         isTyVarName, isDllName, 
27         nameIsLocalOrFrom, isHomePackageName,
28         
29         -- Environment
30         NameEnv, mkNameEnv,
31         emptyNameEnv, unitNameEnv, nameEnvElts, 
32         extendNameEnv_C, extendNameEnv, foldNameEnv, filterNameEnv,
33         plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList,
34         lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, 
35
36
37         -- Class NamedThing and overloaded friends
38         NamedThing(..),
39         getSrcLoc, getOccString, toRdrName
40     ) where
41
42 #include "HsVersions.h"
43
44 import OccName          -- All of it
45 import Module           ( Module, moduleName, mkVanillaModule, isHomeModule )
46 import RdrName          ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule )
47 import CmdLineOpts      ( opt_Static )
48 import SrcLoc           ( builtinSrcLoc, noSrcLoc, SrcLoc )
49 import Unique           ( Unique, Uniquable(..), u2i, pprUnique, pprUnique10 )
50 import FastTypes
51 import Maybes           ( expectJust )
52 import UniqFM
53 import Outputable
54 \end{code}
55
56 %************************************************************************
57 %*                                                                      *
58 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
59 %*                                                                      *
60 %************************************************************************
61  
62 \begin{code}
63 data Name = Name {
64                 n_sort :: NameSort,     -- What sort of name it is
65                 n_occ  :: OccName,      -- Its occurrence name
66                 n_uniq :: Unique,
67                 n_loc  :: SrcLoc        -- Definition site
68             }
69
70 data NameSort
71   = Global Module       -- (a) TyCon, Class, their derived Ids, dfun Id
72                         -- (b) Imported Id
73                         -- (c) Top-level Id in the original source, even if
74                         --      locally defined
75
76   | Local               -- A user-defined Id or TyVar
77                         -- defined in the module being compiled
78
79   | System              -- A system-defined Id or TyVar.  Typically the
80                         -- OccName is very uninformative (like 's')
81 \end{code}
82
83 Notes about the NameSorts:
84
85 1.  Initially, top-level Ids (including locally-defined ones) get Global names, 
86     and all other local Ids get Local names
87
88 2.  Things with a @Global@ name are given C static labels, so they finally
89     appear in the .o file's symbol table.  They appear in the symbol table
90     in the form M.n.  If originally-local things have this property they
91     must be made @Global@ first.
92
93 3.  In the tidy-core phase, a Global that is not visible to an importer
94     is changed to Local, and a Local that is visible is changed to Global
95
96 4.  A System Name differs in the following ways:
97         a) has unique attached when printing dumps
98         b) unifier eliminates sys tyvars in favour of user provs where possible
99
100     Before anything gets printed in interface files or output code, it's
101     fed through a 'tidy' processor, which zaps the OccNames to have
102     unique names; and converts all sys-locals to user locals
103     If any desugarer sys-locals have survived that far, they get changed to
104     "ds1", "ds2", etc.
105
106 \begin{code}
107 nameUnique              :: Name -> Unique
108 nameOccName             :: Name -> OccName 
109 nameModule              :: Name -> Module
110 nameSrcLoc              :: Name -> SrcLoc
111
112 nameUnique  name = n_uniq name
113 nameOccName name = n_occ  name
114 nameSrcLoc  name = n_loc  name
115
116 nameModule (Name { n_sort = Global mod }) = mod
117 nameModule name                           = pprPanic "nameModule" (ppr name)
118
119 nameModule_maybe (Name { n_sort = Global mod }) = Just mod
120 nameModule_maybe name                           = Nothing
121 \end{code}
122
123 \begin{code}
124 nameIsLocalOrFrom       :: Module -> Name -> Bool
125 isLocalName             :: Name -> Bool         -- Not globals
126 isGlobalName            :: Name -> Bool
127 isSystemName            :: Name -> Bool
128 isExternallyVisibleName :: Name -> Bool
129 isHomePackageName       :: Name -> Bool
130
131 isGlobalName (Name {n_sort = Global _}) = True
132 isGlobalName other                      = False
133
134 isLocalName name = not (isGlobalName name)
135
136 nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from
137 nameIsLocalOrFrom from other                        = True
138
139 isHomePackageName (Name {n_sort = Global mod}) = isHomeModule mod
140 isHomePackageName other                        = True   -- Local and system names
141
142 isDllName :: Name -> Bool       -- Does this name refer to something in a different DLL?
143 isDllName nm = not opt_Static && not (isHomePackageName nm)
144
145 isTyVarName :: Name -> Bool
146 isTyVarName name = isTvOcc (nameOccName name)
147
148 -- Global names are by definition those that are visible
149 -- outside the module, *as seen by the linker*.  Externally visible
150 -- does not mean visible at the source level
151 isExternallyVisibleName name = isGlobalName name
152
153 isSystemName (Name {n_sort = System}) = True
154 isSystemName other                    = False
155 \end{code}
156
157
158 %************************************************************************
159 %*                                                                      *
160 \subsection{Making names}
161 %*                                                                      *
162 %************************************************************************
163
164 \begin{code}
165 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
166 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
167         -- NB: You might worry that after lots of huffing and
168         -- puffing we might end up with two local names with distinct
169         -- uniques, but the same OccName.  Indeed we can, but that's ok
170         --      * the insides of the compiler don't care: they use the Unique
171         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
172         --        uniques if you get confused
173         --      * for interface files we tidyCore first, which puts the uniques
174         --        into the print name (see setNameVisibility below)
175
176 mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
177 mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
178                                        n_occ = occ, n_loc = loc }
179
180 mkKnownKeyGlobal :: RdrName -> Unique -> Name
181 mkKnownKeyGlobal rdr_name uniq
182   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
183                       (rdrNameOcc rdr_name)
184                       builtinSrcLoc
185
186 mkWiredInName :: Module -> OccName -> Unique -> Name
187 mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
188
189 mkSysLocalName :: Unique -> UserFS -> Name
190 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
191                                 n_occ = mkVarOcc fs, n_loc = noSrcLoc }
192
193 mkCCallName :: Unique -> EncodedString -> Name
194         -- The encoded string completely describes the ccall
195 mkCCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
196                                n_occ = mkCCallOcc str, n_loc = noSrcLoc }
197
198 mkIPName :: Unique -> OccName -> Name
199 mkIPName uniq occ
200   = Name { n_uniq = uniq,
201            n_sort = Local,
202            n_occ  = occ,
203            n_loc = noSrcLoc }
204 \end{code}
205
206 \begin{code}
207 -- When we renumber/rename things, we need to be
208 -- able to change a Name's Unique to match the cached
209 -- one in the thing it's the name of.  If you know what I mean.
210 setNameUnique name uniq = name {n_uniq = uniq}
211
212 setNameOcc :: Name -> OccName -> Name
213 setNameOcc name occ = name {n_occ = occ}
214
215 globaliseName :: Name -> Module -> Name
216 globaliseName n mod = n { n_sort = Global mod }
217                                 
218 localiseName :: Name -> Name
219 localiseName n = n { n_sort = Local }
220                                 
221 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
222 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
223                        where
224                          set (Global _) = Global mod
225 \end{code}
226
227
228 %************************************************************************
229 %*                                                                      *
230 \subsection{Predicates and selectors}
231 %*                                                                      *
232 %************************************************************************
233
234 \begin{code}
235 hashName :: Name -> Int
236 hashName name = iBox (u2i (nameUnique name))
237
238
239 nameRdrName :: Name -> RdrName
240 -- Makes a qualified name for top-level (Global) names, whether locally defined or not
241 -- and an unqualified name just for Locals
242 nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ
243 nameRdrName (Name { n_occ = occ })                      = mkRdrUnqual occ
244 \end{code}
245
246
247 %************************************************************************
248 %*                                                                      *
249 \subsection[Name-instances]{Instance declarations}
250 %*                                                                      *
251 %************************************************************************
252
253 \begin{code}
254 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
255 \end{code}
256
257 \begin{code}
258 instance Eq Name where
259     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
260     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
261
262 instance Ord Name where
263     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
264     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
265     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
266     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
267     compare a b = cmpName a b
268
269 instance Uniquable Name where
270     getUnique = nameUnique
271
272 instance NamedThing Name where
273     getName n = n
274 \end{code}
275
276
277 %************************************************************************
278 %*                                                                      *
279 \subsection{Name environment}
280 %*                                                                      *
281 %************************************************************************
282
283 \begin{code}
284 type NameEnv a = UniqFM a       -- Domain is Name
285
286 emptyNameEnv     :: NameEnv a
287 mkNameEnv        :: [(Name,a)] -> NameEnv a
288 nameEnvElts      :: NameEnv a -> [a]
289 extendNameEnv_C  :: (a->a->a) -> NameEnv a -> Name -> a -> NameEnv a
290 extendNameEnv    :: NameEnv a -> Name -> a -> NameEnv a
291 plusNameEnv      :: NameEnv a -> NameEnv a -> NameEnv a
292 plusNameEnv_C    :: (a->a->a) -> NameEnv a -> NameEnv a -> NameEnv a
293 extendNameEnvList:: NameEnv a -> [(Name,a)] -> NameEnv a
294 delFromNameEnv   :: NameEnv a -> Name -> NameEnv a
295 elemNameEnv      :: Name -> NameEnv a -> Bool
296 unitNameEnv      :: Name -> a -> NameEnv a
297 lookupNameEnv    :: NameEnv a -> Name -> Maybe a
298 lookupNameEnv_NF :: NameEnv a -> Name -> a
299 mapNameEnv       :: (a->b) -> NameEnv a -> NameEnv b
300 foldNameEnv      :: (a -> b -> b) -> b -> NameEnv a -> b
301 filterNameEnv    :: (elt -> Bool) -> NameEnv elt -> NameEnv elt
302
303 emptyNameEnv     = emptyUFM
304 foldNameEnv      = foldUFM
305 mkNameEnv        = listToUFM
306 nameEnvElts      = eltsUFM
307 extendNameEnv_C  = addToUFM_C
308 extendNameEnv    = addToUFM
309 plusNameEnv      = plusUFM
310 plusNameEnv_C    = plusUFM_C
311 extendNameEnvList= addListToUFM
312 delFromNameEnv   = delFromUFM
313 elemNameEnv      = elemUFM
314 mapNameEnv       = mapUFM
315 unitNameEnv      = unitUFM
316 filterNameEnv    = filterUFM
317
318 lookupNameEnv          = lookupUFM
319 lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupUFM env n)
320 \end{code}
321
322
323 %************************************************************************
324 %*                                                                      *
325 \subsection{Pretty printing}
326 %*                                                                      *
327 %************************************************************************
328
329 \begin{code}
330 instance Outputable Name where
331         -- When printing interfaces, all Locals have been given nice print-names
332     ppr name = pprName name
333
334 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
335   = getPprStyle $ \ sty ->
336     case sort of
337       Global mod -> pprGlobal sty name uniq mod occ
338       System     -> pprSysLocal sty uniq occ
339       Local      -> pprLocal sty uniq occ
340
341 pprGlobal sty name uniq mod occ
342   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
343
344   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
345                             text "{-" <> pprUnique uniq <> text "-}"
346
347   | unqualStyle sty name = pprOccName occ
348   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
349
350 pprLocal sty uniq occ
351   | codeStyle sty  = pprUnique uniq
352   | debugStyle sty = pprOccName occ <> 
353                      text "{-" <> pprUnique uniq <> text "-}"
354   | otherwise      = pprOccName occ     -- User and Iface styles
355
356 -- Like Local, except that we only omit the unique in Iface style
357 pprSysLocal sty uniq occ
358   | codeStyle sty  = pprUnique uniq
359   | ifaceStyle sty = pprOccName occ     -- The tidy phase has ensured that OccNames
360                                         -- are enough
361   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
362                                 -- If the tidy phase hasn't run, the OccName
363                                 -- is unlikely to be informative (like 's'),
364                                 -- so print the unique
365 \end{code}
366
367 %************************************************************************
368 %*                                                                      *
369 \subsection{Overloaded functions related to Names}
370 %*                                                                      *
371 %************************************************************************
372
373 \begin{code}
374 class NamedThing a where
375     getOccName :: a -> OccName
376     getName    :: a -> Name
377
378     getOccName n = nameOccName (getName n)      -- Default method
379 \end{code}
380
381 \begin{code}
382 getSrcLoc           :: NamedThing a => a -> SrcLoc
383 getOccString        :: NamedThing a => a -> String
384 toRdrName           :: NamedThing a => a -> RdrName
385
386 getSrcLoc           = nameSrcLoc           . getName
387 getOccString        = occNameString        . getOccName
388 toRdrName           = nameRdrName          . getName
389 \end{code}
390