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