[project @ 2000-01-28 20:52:37 by lewie]
[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, 
14         mkTopName, mkIPName,
15         mkDerivedName, mkGlobalName, mkKnownKeyGlobal,
16         mkWiredInIdName,   mkWiredInTyConName,
17         maybeWiredInIdName, maybeWiredInTyConName,
18         isWiredInName, hashName,
19
20         nameUnique, setNameUnique, setNameProvenance, getNameProvenance, setNameImportReason,
21         tidyTopName, 
22         nameOccName, nameModule, setNameOcc, nameRdrName, setNameModule,
23
24         isUserExportedName, isUserImportedExplicitlyName, nameSrcLoc,
25         isLocallyDefinedName,
26
27         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
28         
29
30         -- Provenance
31         Provenance(..), ImportReason(..), pprProvenance,
32         ExportFlag(..), PrintUnqualified,
33         pprNameProvenance, hasBetterProv,
34
35         -- Class NamedThing and overloaded friends
36         NamedThing(..),
37         getSrcLoc, isLocallyDefined, getOccString
38     ) where
39
40 #include "HsVersions.h"
41
42 import {-# SOURCE #-} Var   ( Id, setIdName )
43 import {-# SOURCE #-} TyCon ( TyCon, setTyConName )
44
45 import OccName          -- All of it
46 import Module           ( Module, moduleName, pprModule, mkVanillaModule )
47 import RdrName          ( RdrName, mkRdrQual, mkRdrUnqual, rdrNameOcc, rdrNameModule )
48 import CmdLineOpts      ( opt_PprStyle_NoPrags, opt_OmitInterfacePragmas, opt_EnsureSplittableC )
49
50 import SrcLoc           ( noSrcLoc, mkBuiltinSrcLoc, SrcLoc )
51 import Unique           ( pprUnique, Unique, Uniquable(..), u2i )
52 import Outputable
53 import GlaExts
54 \end{code}
55
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_uniq :: Unique,
67                 n_occ  :: OccName,      -- Its occurrence name
68                 n_prov :: Provenance    -- How it was made
69             }
70
71 data NameSort
72   = Local
73   | Global Module
74   | WiredInId Module Id
75   | WiredInTyCon Module TyCon
76 \end{code}
77
78 Things with a @Global@ name are given C static labels, so they finally
79 appear in the .o file's symbol table.  They appear in the symbol table
80 in the form M.n.  If originally-local things have this property they
81 must be made @Global@ first.
82
83 \begin{code}
84 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
85 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, 
86                                   n_prov = LocalDef loc NotExported }
87         -- NB: You might worry that after lots of huffing and
88         -- puffing we might end up with two local names with distinct
89         -- uniques, but the same OccName.  Indeed we can, but that's ok
90         --      * the insides of the compiler don't care: they use the Unique
91         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
92         --        uniques if you get confused
93         --      * for interface files we tidyCore first, which puts the uniques
94         --        into the print name (see setNameVisibility below)
95
96 mkImportedLocalName :: Unique -> OccName -> SrcLoc -> Name
97         -- Just the same as mkLocalName, except the provenance is different
98         -- Reason: this flags the name as one that came in from an interface file.
99         -- This is useful when trying to decide which of two type variables
100         -- should 'win' when unifying them.
101         -- NB: this is only for non-top-level names, so we use ImplicitImport
102 mkImportedLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, 
103                                           n_prov = NonLocalDef ImplicitImport True }
104
105
106 mkGlobalName :: Unique -> Module -> OccName -> Provenance -> Name
107 mkGlobalName uniq mod occ prov = Name { n_uniq = uniq, n_sort = Global mod,
108                                         n_occ = occ, n_prov = prov }
109                                 
110
111 mkKnownKeyGlobal :: (RdrName, Unique) -> Name
112 mkKnownKeyGlobal (rdr_name, uniq)
113   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
114                       (rdrNameOcc rdr_name)
115                       systemProvenance
116
117 mkSysLocalName :: Unique -> UserFS -> Name
118 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = Local, 
119                                 n_occ = mkSrcVarOcc fs, n_prov = systemProvenance }
120
121 mkTopName :: Unique -> Module -> FAST_STRING -> Name
122         -- Make a top-level name; make it Global if top-level
123         -- things should be externally visible; Local otherwise
124         -- This chap is only used *after* the tidyCore phase
125         -- Notably, it is used during STG lambda lifting
126         --
127         -- We have to make sure that the name is globally unique
128         -- and we don't have tidyCore to help us. So we append
129         -- the unique.  Hack!  Hack!
130 mkTopName uniq mod fs
131   = Name { n_uniq = uniq, 
132            n_sort = mk_top_sort mod,
133            n_occ  = mkSrcVarOcc (_PK_ ((_UNPK_ fs) ++ show uniq)),
134            n_prov = LocalDef noSrcLoc NotExported }
135
136 mkIPName :: Unique -> OccName -> Name
137 mkIPName uniq occ
138   = Name { n_uniq = uniq,
139            n_sort = Local,
140            n_occ  = mkIPOcc occ,
141            n_prov = SystemProv }
142
143 ------------------------- Wired in names -------------------------
144
145 mkWiredInIdName :: Unique -> Module -> OccName -> Id -> Name
146 mkWiredInIdName uniq mod occ id = Name { n_uniq = uniq, n_sort = WiredInId mod id,
147                                          n_occ = occ, n_prov = SystemProv }
148
149 -- mkWiredInTyConName takes a FAST_STRING instead of
150 -- an OccName, which is a bit yukky but that's what the 
151 -- clients find easiest.
152 mkWiredInTyConName :: Unique -> Module -> FAST_STRING -> TyCon -> Name
153 mkWiredInTyConName uniq mod fs tycon
154   = Name { n_uniq = uniq, n_sort = WiredInTyCon mod tycon,
155            n_occ = mkSrcOccFS tcName fs, n_prov = SystemProv }
156
157
158 ---------------------------------------------------------------------
159 mkDerivedName :: (OccName -> OccName)
160               -> Name           -- Base name
161               -> Unique         -- New unique
162               -> Name           -- Result is always a value name
163
164 mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)}
165
166 -- When we renumber/rename things, we need to be
167 -- able to change a Name's Unique to match the cached
168 -- one in the thing it's the name of.  If you know what I mean.
169 setNameUnique name uniq = name {n_uniq = uniq}
170
171 setNameOcc :: Name -> OccName -> Name
172         -- Give the thing a new OccName, *and*
173         -- record that it's no longer a sys-local
174         -- This is used by the tidy-up pass
175 setNameOcc name occ = name {n_occ = occ}
176
177 setNameModule :: Name -> Module -> Name
178 setNameModule name mod = name {n_sort = set (n_sort name)}
179                        where
180                          set (Global _)             = Global mod
181                          set (WiredInId _ id)       = WiredInId mod id
182                          set (WiredInTyCon _ tycon) = WiredInTyCon mod tycon
183 \end{code}
184
185
186 %************************************************************************
187 %*                                                                      *
188 \subsection{Setting provenance and visibility
189 %*                                                                      *
190 %************************************************************************
191
192 tidyTopName is applied to top-level names in the final program
193
194 For top-level things, it globalises Local names 
195                                 (if all top-level things should be visible)
196                          and localises non-exported Global names
197                                  (if only exported things should be visible)
198
199 In all cases except an exported global, it gives it a new occurrence name.
200
201 The "visibility" here concerns whether the .o file's symbol table
202 mentions the thing; if so, it needs a module name in its symbol.
203 The Global things are "visible" and the Local ones are not
204
205 Why should things be "visible"?  Certainly they must be if they
206 are exported.  But also:
207
208 (a) In certain (prelude only) modules we split up the .hc file into
209     lots of separate little files, which are separately compiled by the C
210     compiler.  That gives lots of little .o files.  The idea is that if
211     you happen to mention one of them you don't necessarily pull them all
212     in.  (Pulling in a piece you don't need can be v bad, because it may
213     mention other pieces you don't need either, and so on.)
214     
215     Sadly, splitting up .hc files means that local names (like s234) are
216     now globally visible, which can lead to clashes between two .hc
217     files. So unlocaliseWhatnot goes through making all the local things
218     into global things, essentially by giving them full names so when they
219     are printed they'll have their module name too.  Pretty revolting
220     really.
221
222 (b) When optimisation is on we want to make all the internal
223     top-level defns externally visible
224
225 \begin{code}
226 tidyTopName :: Module -> TidyOccEnv -> Name -> (TidyOccEnv, Name)
227 tidyTopName mod env name
228   = (env', name')
229   where
230     (env', occ') = tidyOccName env (n_occ name)
231
232     name'        = Name { n_uniq = n_uniq name, n_sort = mk_top_sort mod,
233                           n_occ = occ', n_prov = LocalDef noSrcLoc NotExported }
234
235 mk_top_sort mod | all_toplev_ids_visible = Global mod
236                 | otherwise              = Local
237
238 all_toplev_ids_visible = 
239         not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
240         opt_EnsureSplittableC            -- Splitting requires visiblilty
241 \end{code}
242
243 \begin{code}
244 setNameProvenance :: Name -> Provenance -> Name 
245         -- setNameProvenance used to only change the provenance of 
246         -- Implicit-provenance things, but that gives bad error messages 
247         -- for names defined twice in the same module, so I changed it to 
248         -- set the provenance of *any* global (SLPJ Jun 97)
249 setNameProvenance name prov = name {n_prov = prov}
250
251 getNameProvenance :: Name -> Provenance
252 getNameProvenance name = n_prov name
253
254 setNameImportReason :: Name -> ImportReason -> Name
255 setNameImportReason name reason
256   = name { n_prov = new_prov }
257   where
258         -- It's important that we don't do the pattern matching
259         -- in the top-level clause, else we get a black hole in 
260         -- the renamer.  Rather a yukky constraint.  There's only
261         -- one call, in RnNames
262     old_prov = n_prov name
263     new_prov = case old_prov of
264                   NonLocalDef _ omit -> NonLocalDef reason omit
265                   other              -> old_prov
266 \end{code}
267
268
269 %************************************************************************
270 %*                                                                      *
271 \subsection{Provenance and export info}
272 %*                                                                      *
273 %************************************************************************
274
275 \begin{code}
276 data Provenance
277   = LocalDef                    -- Defined locally
278         SrcLoc                  -- Defn site
279         ExportFlag              -- Whether it's exported
280
281   | NonLocalDef                 -- Defined non-locally
282         ImportReason
283         PrintUnqualified
284
285   | SystemProv                  -- Either (a) a system-generated local with 
286                                 --            a v short name OccName
287                                 -- or     (b) a known-key global which should have a proper
288                                 --            provenance attached by the renamer
289 \end{code}
290
291 Sys-provs are only used internally.  When the compiler generates (say)
292 a fresh desguar variable it always calls it "ds", and of course it gets
293 a fresh unique.  But when printing -ddump-xx dumps, we must print it with
294 its unique, because there'll be a lot of "ds" variables.
295
296 Names with SystemProv differ in the following ways:
297         a) locals have unique attached when printing dumps
298         b) unifier eliminates sys tyvars in favour of user provs where possible
299         c) renamer replaces SystemProv with a better one
300
301 Before anything gets printed in interface files or output code, it's
302 fed through a 'tidy' processor, which zaps the OccNames to have
303 unique names; and converts all sys-locals to user locals
304 If any desugarer sys-locals have survived that far, they get changed to
305 "ds1", "ds2", etc.
306
307 \begin{code}
308 data ImportReason
309   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
310                                         -- Note the M may well not be the defining module
311                                         -- for this thing!
312         -- The Bool is true iff the thing was named *explicitly* in the import spec,
313         -- rather than being imported as part of a group; e.g.
314         --      import B
315         --      import C( T(..) )
316         -- Here, everything imported by B, and the constructors of T
317         -- are not named explicitly; only T is named explicitly.
318         -- This info is used when warning of unused names.
319
320   | ImplicitImport                      -- Imported implicitly for some other reason
321                         
322
323 type PrintUnqualified = Bool    -- True <=> the unqualified name of this thing is
324                                 -- in scope in this module, so print it 
325                                 -- unqualified in error messages
326
327 data ExportFlag = Exported  | NotExported
328 \end{code}
329
330 Something is "Exported" if it may be mentioned by another module without
331 warning.  The crucial thing about Exported things is that they must
332 never be dropped as dead code, even if they aren't used in this module.
333 Furthermore, being Exported means that we can't see all call sites of the thing.
334
335 Exported things include:
336
337         - explicitly exported Ids, including data constructors, 
338           class method selectors
339
340         - dfuns from instance decls
341
342 Being Exported is *not* the same as finally appearing in the .o file's 
343 symbol table.  For example, a local Id may be mentioned in an Exported
344 Id's unfolding in the interface file, in which case the local Id goes
345 out too.
346
347
348 \begin{code}
349 systemProvenance :: Provenance
350 systemProvenance = SystemProv
351
352 -- pprNameProvenance is used in error messages to say where a name came from
353 pprNameProvenance :: Name -> SDoc
354 pprNameProvenance name = pprProvenance (getNameProvenance name)
355
356 pprProvenance :: Provenance -> SDoc
357 pprProvenance SystemProv             = ptext SLIT("System")
358 pprProvenance (LocalDef loc _)       = ptext SLIT("defined at")    <+> ppr loc
359 pprProvenance (NonLocalDef ImplicitImport _)
360   = ptext SLIT("implicitly imported")
361 pprProvenance (NonLocalDef (UserImport mod loc _) _) 
362   =  ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
363 \end{code}
364
365
366 %************************************************************************
367 %*                                                                      *
368 \subsection{Predicates and selectors}
369 %*                                                                      *
370 %************************************************************************
371
372 \begin{code}
373 nameUnique              :: Name -> Unique
374 nameOccName             :: Name -> OccName 
375 nameModule              :: Name -> Module
376 nameSrcLoc              :: Name -> SrcLoc
377 isLocallyDefinedName    :: Name -> Bool
378 isUserExportedName      :: Name -> Bool
379 isWiredInName           :: Name -> Bool
380 isLocalName             :: Name -> Bool
381 isGlobalName            :: Name -> Bool
382 isExternallyVisibleName :: Name -> Bool
383
384
385
386 hashName :: Name -> Int
387 hashName name = IBOX( u2i (nameUnique name) )
388
389 nameUnique name = n_uniq name
390 nameOccName name = n_occ name
391
392 nameModule name =
393   case n_sort name of
394     Local -> pprPanic "nameModule" (ppr name)
395     x     -> nameSortModule x
396
397 nameSortModule (Global       mod)   = mod
398 nameSortModule (WiredInId    mod _) = mod
399 nameSortModule (WiredInTyCon mod _) = mod
400
401 nameRdrName :: Name -> RdrName
402 nameRdrName (Name { n_sort = Local, n_occ = occ }) = mkRdrUnqual occ
403 nameRdrName (Name { n_sort = sort,  n_occ = occ }) = mkRdrQual (moduleName (nameSortModule sort)) occ
404
405 isUserExportedName (Name { n_prov = LocalDef _ Exported }) = True
406 isUserExportedName other                                   = False
407
408 isUserImportedExplicitlyName (Name { n_prov = NonLocalDef (UserImport _ _ explicit) _ }) = explicit
409 isUserImportedExplicitlyName other                                                       = False
410
411 nameSrcLoc name = provSrcLoc (n_prov name)
412
413 provSrcLoc (LocalDef loc _)                     = loc        
414 provSrcLoc (NonLocalDef (UserImport _ loc _) _) = loc
415 provSrcLoc other                                = noSrcLoc   
416   
417 isLocallyDefinedName (Name {n_sort = Local})        = True      -- Local (might have SystemProv)
418 isLocallyDefinedName (Name {n_prov = LocalDef _ _}) = True      -- Global, but defined here
419 isLocallyDefinedName other                          = False     -- Other
420
421 -- Things the compiler "knows about" are in some sense
422 -- "imported".  When we are compiling the module where
423 -- the entities are defined, we need to be able to pick
424 -- them out, often in combination with isLocallyDefined.
425 isWiredInName (Name {n_sort = WiredInTyCon _ _}) = True
426 isWiredInName (Name {n_sort = WiredInId    _ _}) = True
427 isWiredInName _                                  = False
428
429 maybeWiredInIdName :: Name -> Maybe Id
430 maybeWiredInIdName (Name {n_sort = WiredInId _ id}) = Just id
431 maybeWiredInIdName other                            = Nothing
432
433 maybeWiredInTyConName :: Name -> Maybe TyCon
434 maybeWiredInTyConName (Name {n_sort = WiredInTyCon _ tc}) = Just tc
435 maybeWiredInTyConName other                               = Nothing
436
437
438 isLocalName (Name {n_sort = Local}) = True
439 isLocalName _                       = False
440
441 isGlobalName (Name {n_sort = Local}) = False
442 isGlobalName other                   = True
443
444 -- Global names are by definition those that are visible
445 -- outside the module, *as seen by the linker*.  Externally visible
446 -- does not mean visible at the source level (that's isExported).
447 isExternallyVisibleName name = isGlobalName name
448
449 hasBetterProv :: Name -> Name -> Bool
450 hasBetterProv name1 name2
451   = case n_prov name1 of
452         LocalDef _ _    -> True
453         SystemProv      -> False
454         NonLocalDef _ _ -> case n_prov name2 of
455                                 LocalDef _ _ -> False
456                                 other        -> True
457
458 isSystemName (Name {n_prov = SystemProv}) = True
459 isSystemName other                        = False
460 \end{code}
461
462
463 %************************************************************************
464 %*                                                                      *
465 \subsection[Name-instances]{Instance declarations}
466 %*                                                                      *
467 %************************************************************************
468
469 \begin{code}
470 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
471 \end{code}
472
473 \begin{code}
474 instance Eq Name where
475     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
476     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
477
478 instance Ord Name where
479     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
480     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
481     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
482     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
483     compare a b = cmpName a b
484
485 instance Uniquable Name where
486     getUnique = nameUnique
487
488 instance NamedThing Name where
489     getName n = n
490 \end{code}
491
492
493 %************************************************************************
494 %*                                                                      *
495 \subsection{Pretty printing}
496 %*                                                                      *
497 %************************************************************************
498
499 \begin{code}
500 instance Outputable Name where
501         -- When printing interfaces, all Locals have been given nice print-names
502     ppr name = pprName name
503
504 pprName (Name {n_sort = Local, n_uniq = uniq, n_occ = occ, n_prov = prov})
505         -- Locals
506   = getPprStyle $ \ sty ->
507     if codeStyle sty then
508         pprUnique uniq          -- When printing in code we required all names to 
509                                 -- be globally unique; for example, we use this identifier
510                                 -- for the closure name.  So we just print the unique alone.
511     else
512         pprOccName occ <> pp_local_extra sty uniq
513   where
514     sys_local = case prov of
515                   SystemProv -> True
516                   other      -> False
517
518     pp_local_extra sty uniq
519         | sys_local      = underscore <> pprUnique uniq         -- Must print uniques for sys_locals
520         | debugStyle sty = text "{-" <> pprUnique uniq <> text "-}"
521         | otherwise      = empty
522
523
524 pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ, n_prov = prov})
525         -- Globals, and wired in things
526   = getPprStyle $ \ sty ->
527     if codeStyle sty then
528         ppr mod <> underscore <> ppr occ
529     else
530         pp_mod_dot sty <> ppr occ <> pp_global_debug sty uniq prov
531   where
532     mod = nameSortModule sort
533
534     pp_mod_dot sty
535       = case prov of
536            SystemProv                                -> pp_qual mod user_sty
537                 -- Hack alert!  Omit the qualifier on SystemProv things in user style
538                 -- I claim such SystemProv things will also be WiredIn things.
539                 -- We can't get the omit flag right
540                 -- on wired in tycons etc (sigh) so we just leave it out in user style, 
541                 -- and hope that leaving it out isn't too consfusing.
542                 -- (e.g. if the programmer hides Bool and  redefines it.  If so, use -dppr-debug.)
543
544            LocalDef _ _                              -> pp_qual mod (user_sty || iface_sty)
545
546            NonLocalDef (UserImport imp_mod _ _) omit 
547                 | user_sty                           -> pp_qual imp_mod omit
548                 | otherwise                          -> pp_qual mod     False
549            NonLocalDef ImplicitImport           omit -> pp_qual mod     (user_sty && omit)
550       where
551         user_sty  = userStyle sty
552         iface_sty = ifaceStyle sty
553     
554     pp_qual mod omit_qual
555         | omit_qual  = empty
556         | otherwise  = pprModule mod <> dot
557     
558     pp_global_debug sty uniq prov
559       | debugStyle sty = hcat [text "{-", pprUnique uniq, prov_p prov, text "-}"]
560       | otherwise      = empty
561
562     prov_p prov | opt_PprStyle_NoPrags = empty
563                 | otherwise            = comma <> pp_prov prov
564
565 pp_prov (LocalDef _ Exported)          = char 'x'
566 pp_prov (LocalDef _ NotExported)       = char 'l'
567 pp_prov (NonLocalDef ImplicitImport _) = char 'j'
568 pp_prov (NonLocalDef (UserImport _ _ True ) _) = char 'I'       -- Imported by name
569 pp_prov (NonLocalDef (UserImport _ _ False) _) = char 'i'       -- Imported by ..
570 pp_prov SystemProv                     = char 's'
571 \end{code}
572
573
574 %************************************************************************
575 %*                                                                      *
576 \subsection{Overloaded functions related to Names}
577 %*                                                                      *
578 %************************************************************************
579
580 \begin{code}
581 class NamedThing a where
582     getOccName :: a -> OccName
583     getName    :: a -> Name
584
585     getOccName n = nameOccName (getName n)      -- Default method
586 \end{code}
587
588 \begin{code}
589 getSrcLoc           :: NamedThing a => a -> SrcLoc
590 isLocallyDefined    :: NamedThing a => a -> Bool
591 getOccString        :: NamedThing a => a -> String
592
593 getSrcLoc           = nameSrcLoc           . getName
594 isLocallyDefined    = isLocallyDefinedName . getName
595 getOccString x      = occNameString (getOccName x)
596 \end{code}
597
598 \begin{code}
599 {-# SPECIALIZE isLocallyDefined :: Name -> Bool #-}
600 \end{code}