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