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