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