[project @ 2000-11-14 08:07:11 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         mkTopName, mkIPName,
15         mkDerivedName, mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
16
17         nameUnique, setNameUnique,
18         tidyTopName, 
19         nameOccName, nameModule, nameModule_maybe,
20         setNameOcc, nameRdrName, setNameModuleAndLoc, 
21         toRdrName, hashName,
22
23         nameSrcLoc, nameIsLocallyDefined, isDllName, nameIsFrom, nameIsLocalOrFrom,
24
25         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
26         isTyVarName,
27         
28         -- Environment
29         NameEnv, mkNameEnv,
30         emptyNameEnv, unitNameEnv, nameEnvElts, 
31         extendNameEnv_C, extendNameEnv, foldNameEnv,
32         plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList,
33         lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, 
34
35
36         -- Class NamedThing and overloaded friends
37         NamedThing(..),
38         getSrcLoc, getOccString, toRdrName,
39         isFrom, isLocalOrFrom
40     ) where
41
42 #include "HsVersions.h"
43
44 import OccName          -- All of it
45 import Module           ( Module, moduleName, mkVanillaModule, isModuleInThisPackage )
46 import RdrName          ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule )
47 import CmdLineOpts      ( opt_Static, opt_OmitInterfacePragmas, opt_EnsureSplittableC )
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 nameIsLocallyDefined    :: Name -> Bool
125 nameIsFrom              :: Module -> Name -> Bool
126 nameIsLocalOrFrom       :: Module -> Name -> Bool
127 isLocalName             :: Name -> Bool         -- Not globals
128 isGlobalName            :: Name -> Bool
129 isSystemName            :: Name -> Bool
130 isExternallyVisibleName :: Name -> Bool
131
132 isGlobalName (Name {n_sort = Global _}) = True
133 isGlobalName other                      = False
134
135 isLocalName name = not (isGlobalName name)
136
137 nameIsLocallyDefined name = isLocalName name
138
139 nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from
140 nameIsLocalOrFrom from other                        = True
141
142 nameIsFrom from (Name {n_sort = Global mod}) = mod == from
143 nameIsFrom from other                        = pprPanic "nameIsFrom" (ppr other)
144
145 -- Global names are by definition those that are visible
146 -- outside the module, *as seen by the linker*.  Externally visible
147 -- does not mean visible at the source level
148 isExternallyVisibleName name = isGlobalName name
149
150 isSystemName (Name {n_sort = System}) = True
151 isSystemName other                    = False
152 \end{code}
153
154
155 %************************************************************************
156 %*                                                                      *
157 \subsection{Making names}
158 %*                                                                      *
159 %************************************************************************
160
161 \begin{code}
162 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
163 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
164         -- NB: You might worry that after lots of huffing and
165         -- puffing we might end up with two local names with distinct
166         -- uniques, but the same OccName.  Indeed we can, but that's ok
167         --      * the insides of the compiler don't care: they use the Unique
168         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
169         --        uniques if you get confused
170         --      * for interface files we tidyCore first, which puts the uniques
171         --        into the print name (see setNameVisibility below)
172
173 mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
174 mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
175                                        n_occ = occ, n_loc = loc }
176                                 
177
178 mkKnownKeyGlobal :: RdrName -> Unique -> Name
179 mkKnownKeyGlobal rdr_name uniq
180   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
181                       (rdrNameOcc rdr_name)
182                       builtinSrcLoc
183
184 mkWiredInName :: Module -> OccName -> Unique -> Name
185 mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
186
187 mkSysLocalName :: Unique -> UserFS -> Name
188 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
189                                 n_occ = mkVarOcc fs, n_loc = noSrcLoc }
190
191 mkCCallName :: Unique -> EncodedString -> Name
192         -- The encoded string completely describes the ccall
193 mkCCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
194                                n_occ = mkCCallOcc str, n_loc = noSrcLoc }
195
196 mkIPName :: Unique -> OccName -> Name
197 mkIPName uniq occ
198   = Name { n_uniq = uniq,
199            n_sort = Local,
200            n_occ  = occ,
201            n_loc = noSrcLoc }
202
203 ---------------------------------------------------------------------
204 mkDerivedName :: (OccName -> OccName)
205               -> Name           -- Base name
206               -> Unique         -- New unique
207               -> Name           -- Result is always a value name
208
209 mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)}
210 \end{code}
211
212 \begin{code}
213 -- When we renumber/rename things, we need to be
214 -- able to change a Name's Unique to match the cached
215 -- one in the thing it's the name of.  If you know what I mean.
216 setNameUnique name uniq = name {n_uniq = uniq}
217
218 setNameOcc :: Name -> OccName -> Name
219         -- Give the thing a new OccName, *and*
220         -- record that it's no longer a sys-local
221         -- This is used by the tidy-up pass
222 setNameOcc name occ = name {n_occ = occ}
223
224 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
225 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
226                        where
227                          set (Global _) = Global mod
228 \end{code}
229
230
231 %************************************************************************
232 %*                                                                      *
233 \subsection{Tidying a name}
234 %*                                                                      *
235 %************************************************************************
236
237 tidyTopName is applied to top-level names in the final program
238
239 For top-level things, 
240         it globalises Local names 
241                 (if all top-level things should be visible)
242         and localises non-exported Global names
243                  (if only exported things should be visible)
244
245 In all cases except an exported global, it gives it a new occurrence name.
246
247 The "visibility" here concerns whether the .o file's symbol table
248 mentions the thing; if so, it needs a module name in its symbol.
249 The Global things are "visible" and the Local ones are not
250
251 Why should things be "visible"?  Certainly they must be if they
252 are exported.  But also:
253
254 (a) In certain (prelude only) modules we split up the .hc file into
255     lots of separate little files, which are separately compiled by the C
256     compiler.  That gives lots of little .o files.  The idea is that if
257     you happen to mention one of them you don't necessarily pull them all
258     in.  (Pulling in a piece you don't need can be v bad, because it may
259     mention other pieces you don't need either, and so on.)
260     
261     Sadly, splitting up .hc files means that local names (like s234) are
262     now globally visible, which can lead to clashes between two .hc
263     files. So unlocaliseWhatnot goes through making all the local things
264     into global things, essentially by giving them full names so when they
265     are printed they'll have their module name too.  Pretty revolting
266     really.
267
268 (b) When optimisation is on we want to make all the internal
269     top-level defns externally visible
270
271 \begin{code}
272 tidyTopName :: Module -> TidyOccEnv -> Bool -> Name -> (TidyOccEnv, Name)
273 tidyTopName mod env is_exported
274             name@(Name { n_occ = occ, n_sort = sort, n_uniq = uniq, n_loc = loc })
275   = case sort of
276         Global _ | is_exported -> (env, name)
277                  | otherwise   -> (env, name { n_sort = new_sort })
278
279         other    | is_exported -> (env', name { n_sort = Global mod, n_occ = occ' })
280                  | otherwise   -> (env', name { n_sort = new_sort,   n_occ = occ' })
281   where
282     (env', occ') = tidyOccName env occ
283     new_sort     = mkLocalTopSort mod
284
285 mkTopName :: Unique -> Module -> FAST_STRING -> Name
286         -- Make a top-level name; make it Global if top-level
287         -- things should be externally visible; Local otherwise
288         -- This chap is only used *after* the tidyCore phase
289         -- Notably, it is used during STG lambda lifting
290         --
291         -- We have to make sure that the name is globally unique
292         -- and we don't have tidyCore to help us. So we append
293         -- the unique.  Hack!  Hack!
294         -- (Used only by the STG lambda lifter.)
295 mkTopName uniq mod fs
296   = Name { n_uniq = uniq, 
297            n_sort = mkLocalTopSort mod,
298            n_occ  = mkVarOcc (_PK_ ((_UNPK_ fs) ++ show uniq)),
299            n_loc = noSrcLoc }
300
301 mkLocalTopSort :: Module -> NameSort
302 mkLocalTopSort mod
303   | all_toplev_ids_visible = Global mod
304   | otherwise              = Local
305
306 all_toplev_ids_visible
307   = not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
308     opt_EnsureSplittableC            -- Splitting requires visiblilty
309 \end{code}
310
311
312
313 %************************************************************************
314 %*                                                                      *
315 \subsection{Predicates and selectors}
316 %*                                                                      *
317 %************************************************************************
318
319 \begin{code}
320 hashName :: Name -> Int
321 hashName name = iBox (u2i (nameUnique name))
322
323
324 nameRdrName :: Name -> RdrName
325 -- Makes a qualified name for top-level (Global) names, whether locally defined or not
326 -- and an unqualified name just for Locals
327 nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ
328 nameRdrName (Name { n_occ = occ })                      = mkRdrUnqual occ
329
330 isDllName :: Name -> Bool
331         -- Does this name refer to something in a different DLL?
332 isDllName nm = not opt_Static &&
333                not (isLocalName nm) &&                          -- isLocalName test needed 'cos
334                not (isModuleInThisPackage (nameModule nm))      -- nameModule won't work on local names
335
336
337
338 isTyVarName :: Name -> Bool
339 isTyVarName name = isTvOcc (nameOccName name)
340
341 \end{code}
342
343
344 %************************************************************************
345 %*                                                                      *
346 \subsection[Name-instances]{Instance declarations}
347 %*                                                                      *
348 %************************************************************************
349
350 \begin{code}
351 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
352 \end{code}
353
354 \begin{code}
355 instance Eq Name where
356     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
357     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
358
359 instance Ord Name where
360     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
361     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
362     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
363     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
364     compare a b = cmpName a b
365
366 instance Uniquable Name where
367     getUnique = nameUnique
368
369 instance NamedThing Name where
370     getName n = n
371 \end{code}
372
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection{Name environment}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381 type NameEnv a = UniqFM a       -- Domain is Name
382
383 emptyNameEnv     :: NameEnv a
384 mkNameEnv        :: [(Name,a)] -> NameEnv a
385 nameEnvElts      :: NameEnv a -> [a]
386 extendNameEnv_C  :: (a->a->a) -> NameEnv a -> Name -> a -> NameEnv a
387 extendNameEnv    :: NameEnv a -> Name -> a -> NameEnv a
388 plusNameEnv      :: NameEnv a -> NameEnv a -> NameEnv a
389 plusNameEnv_C    :: (a->a->a) -> NameEnv a -> NameEnv a -> NameEnv a
390 extendNameEnvList:: NameEnv a -> [(Name,a)] -> NameEnv a
391 delFromNameEnv   :: NameEnv a -> Name -> NameEnv a
392 elemNameEnv      :: Name -> NameEnv a -> Bool
393 unitNameEnv      :: Name -> a -> NameEnv a
394 lookupNameEnv    :: NameEnv a -> Name -> Maybe a
395 lookupNameEnv_NF :: NameEnv a -> Name -> a
396 mapNameEnv       :: (a->b) -> NameEnv a -> NameEnv b
397 foldNameEnv      :: (a -> b -> b) -> b -> NameEnv a -> b
398
399 emptyNameEnv     = emptyUFM
400 foldNameEnv      = foldUFM
401 mkNameEnv        = listToUFM
402 nameEnvElts      = eltsUFM
403 extendNameEnv_C  = addToUFM_C
404 extendNameEnv    = addToUFM
405 plusNameEnv      = plusUFM
406 plusNameEnv_C    = plusUFM_C
407 extendNameEnvList= addListToUFM
408 delFromNameEnv   = delFromUFM
409 elemNameEnv      = elemUFM
410 mapNameEnv       = mapUFM
411 unitNameEnv      = unitUFM
412
413 lookupNameEnv          = lookupUFM
414 lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupUFM env n)
415 \end{code}
416
417
418 %************************************************************************
419 %*                                                                      *
420 \subsection{Pretty printing}
421 %*                                                                      *
422 %************************************************************************
423
424 \begin{code}
425 instance Outputable Name where
426         -- When printing interfaces, all Locals have been given nice print-names
427     ppr name = pprName name
428
429 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
430   = getPprStyle $ \ sty ->
431     case sort of
432       Global mod -> pprGlobal sty name uniq mod occ
433       System     -> pprSysLocal sty uniq occ
434       Local      -> pprLocal sty uniq occ
435
436 pprLocal sty uniq occ
437   | codeStyle sty  = pprUnique uniq
438   | debugStyle sty = pprOccName occ <> 
439                      text "{-" <> pprUnique10 uniq <> text "-}"
440   | otherwise      = pprOccName occ
441
442 pprGlobal sty name uniq mod occ
443   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
444
445   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
446                             text "{-" <> pprUnique10 uniq <> text "-}"
447
448   | unqualStyle sty name = pprOccName occ
449   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
450
451 pprSysLocal sty uniq occ
452   | codeStyle sty  = pprUnique uniq
453   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
454 \end{code}
455
456
457 %************************************************************************
458 %*                                                                      *
459 \subsection{Overloaded functions related to Names}
460 %*                                                                      *
461 %************************************************************************
462
463 \begin{code}
464 class NamedThing a where
465     getOccName :: a -> OccName
466     getName    :: a -> Name
467
468     getOccName n = nameOccName (getName n)      -- Default method
469 \end{code}
470
471 \begin{code}
472 getSrcLoc           :: NamedThing a => a -> SrcLoc
473 getOccString        :: NamedThing a => a -> String
474 toRdrName           :: NamedThing a => a -> RdrName
475 isFrom              :: NamedThing a => Module -> a -> Bool
476 isLocalOrFrom       :: NamedThing a => Module -> a -> Bool
477
478 getSrcLoc           = nameSrcLoc           . getName
479 getOccString        = occNameString        . getOccName
480 toRdrName           = nameRdrName          . getName
481 isFrom mod x        = nameIsFrom mod (getName x)
482 isLocalOrFrom mod x = nameIsLocalOrFrom mod ( getName x)
483 \end{code}
484