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