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