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