[project @ 1998-12-02 13:17:09 by simonm]
[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 Module type
9         Module,
10         pprModule, moduleString,
11
12         -- The basic form of names
13         isLexCon, isLexVar, isLexId, isLexSym,
14         isLexConId, isLexConSym, isLexVarId, isLexVarSym,
15         mkTupNameStr, mkUbxTupNameStr, isLowerISO, isUpperISO,
16
17         -- The OccName type
18         OccName(..), varOcc, 
19         pprOccName, occNameString, occNameFlavour, 
20         isTvOcc, isTCOcc, isVarOcc, prefixOccName,
21
22         -- The Name type
23         Name,                                   -- Abstract
24         mkLocalName, mkSysLocalName, 
25
26         mkCompoundName, mkGlobalName,
27
28         mkWiredInIdName,   mkWiredInTyConName,
29         maybeWiredInIdName, maybeWiredInTyConName,
30         isWiredInName,
31
32         nameUnique, changeUnique, setNameProvenance, getNameProvenance,
33         setNameVisibility, mkNameVisible,
34         nameOccName, nameModule,
35
36         isExportedName, nameSrcLoc,
37         isLocallyDefinedName,
38
39         isSysLocalName, isLocalName, isGlobalName, isExternallyVisibleName,
40
41         pprNameProvenance,
42
43         -- Special Names
44         dictNamePrefix, mkSuperDictSelName, mkWorkerName,
45         mkDefaultMethodName, mkClassTyConStr, mkClassDataConStr,
46
47         -- Misc
48         Provenance(..), pprProvenance,
49         ExportFlag(..), 
50         PrintUnqualified,
51
52         -- Class NamedThing and overloaded friends
53         NamedThing(..),
54         modAndOcc, isExported, 
55         getSrcLoc, isLocallyDefined, getOccString
56     ) where
57
58 #include "HsVersions.h"
59
60 import {-# SOURCE #-} Var   ( Id )
61 import {-# SOURCE #-} TyCon ( TyCon )
62
63 import CStrings         ( identToC )
64 import PrelMods         ( pREL_BASE, pREL_TUP, pREL_GHC )
65 import CmdLineOpts      ( opt_PprStyle_NoPrags, opt_OmitInterfacePragmas, opt_EnsureSplittableC )
66 import BasicTypes       ( Module, IfaceFlavour(..), moduleString, pprModule )
67
68 import SrcLoc           ( noSrcLoc, mkBuiltinSrcLoc, SrcLoc )
69 import Unique           ( pprUnique, Unique, Uniquable(..) )
70 import Outputable
71 import Char             ( isUpper, isLower, ord )
72 import Util             ( nOfThem )
73 import GlaExts
74 \end{code}
75
76
77 %************************************************************************
78 %*                                                                      *
79 \subsection{Lexical categories}
80 %*                                                                      *
81 %************************************************************************
82
83 These functions test strings to see if they fit the lexical categories
84 defined in the Haskell report.
85
86 \begin{code}
87 isLexCon, isLexVar, isLexId, isLexSym, isLexConId, isLexConSym,
88  isLexVarId, isLexVarSym  :: FAST_STRING -> Bool
89
90 isLexCon cs = isLexConId  cs || isLexConSym cs
91 isLexVar cs = isLexVarId  cs || isLexVarSym cs
92
93 isLexId  cs = isLexConId  cs || isLexVarId  cs
94 isLexSym cs = isLexConSym cs || isLexVarSym cs
95
96 -------------
97
98 isLexConId cs
99   | _NULL_ cs        = False
100   | cs == SLIT("[]") = True
101   | c  == '('        = True     -- (), (,), (,,), ...
102   | otherwise        = isUpper c || isUpperISO c
103   where                                 
104     c = _HEAD_ cs
105
106 isLexVarId cs
107   | _NULL_ cs    = False
108   | otherwise    = isLower c || isLowerISO c
109   where
110     c = _HEAD_ cs
111
112 isLexConSym cs
113   | _NULL_ cs   = False
114   | otherwise   = c  == ':'
115                || cs == SLIT("->")
116   where
117     c = _HEAD_ cs
118
119 isLexVarSym cs
120   | _NULL_ cs = False
121   | otherwise = isSymbolASCII c
122              || isSymbolISO c
123   where
124     c = _HEAD_ cs
125
126 -------------
127 isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
128 isSymbolISO   c = ord c `elem` (0xd7 : 0xf7 : [0xa1 .. 0xbf])
129 isUpperISO    (C# c#) = c# `geChar#` '\xc0'# && c# `leChar#` '\xde'# && c# `neChar#` '\xd7'#
130 --0xc0 <= oc && oc <= 0xde && oc /= 0xd7 where oc = ord c
131 isLowerISO    (C# c#) = c# `geChar#` '\xdf'# && c# `leChar#` '\xff'# && c# `neChar#` '\xf7'#
132 --0xdf <= oc && oc <= 0xff && oc /= 0xf7 where oc = ord c
133 \end{code}
134
135 \begin{code}
136 mkTupNameStr 0 = (pREL_BASE, SLIT("()"))
137 mkTupNameStr 1 = panic "Name.mkTupNameStr: 1 ???"
138 mkTupNameStr 2 = (pREL_TUP, _PK_ "(,)")   -- not strictly necessary
139 mkTupNameStr 3 = (pREL_TUP, _PK_ "(,,)")  -- ditto
140 mkTupNameStr 4 = (pREL_TUP, _PK_ "(,,,)") -- ditto
141 mkTupNameStr n = (pREL_TUP, _PK_ ("(" ++ nOfThem (n-1) ',' ++ ")"))
142
143 mkUbxTupNameStr 0 = panic "Name.mkUbxTupNameStr: 0 ???"
144 mkUbxTupNameStr 1 = (pREL_GHC, _PK_ "(# #)") -- 1 and 0 both make sense!!!
145 mkUbxTupNameStr 2 = (pREL_GHC, _PK_ "(#,#)")
146 mkUbxTupNameStr 3 = (pREL_GHC, _PK_ "(#,,#)")
147 mkUbxTupNameStr 4 = (pREL_GHC, _PK_ "(#,,,#)")
148 mkUbxTupNameStr n = (pREL_GHC, _PK_ ("(#" ++ nOfThem (n-1) ',' ++ "#)"))
149 \end{code}
150
151
152 %************************************************************************
153 %*                                                                      *
154 \subsection[Name-pieces-datatypes]{The @OccName@ datatypes}
155 %*                                                                      *
156 %************************************************************************
157
158 \begin{code}
159 data OccName  = VarOcc  FAST_STRING     -- Variables and data constructors
160               | TvOcc   FAST_STRING     -- Type variables
161               | TCOcc   FAST_STRING     -- Type constructors and classes
162
163 pprOccName :: OccName -> SDoc
164 pprOccName n = getPprStyle $ \ sty ->
165                if codeStyle sty 
166                then identToC (occNameString n)
167                else ptext (occNameString n)
168
169 varOcc :: FAST_STRING -> OccName
170 varOcc = VarOcc
171
172 occNameString :: OccName -> FAST_STRING
173 occNameString (VarOcc s)  = s
174 occNameString (TvOcc s)   = s
175 occNameString (TCOcc s)   = s
176
177 mapOccName :: (FAST_STRING -> FAST_STRING) -> OccName -> OccName
178 mapOccName f (VarOcc s) = VarOcc (f s)
179 mapOccName f (TvOcc s)  = TvOcc  (f s)
180 mapOccName f (TCOcc s)  = TCOcc  (f s)
181
182 prefixOccName :: FAST_STRING -> OccName -> OccName
183 prefixOccName prefix (VarOcc s) = VarOcc (prefix _APPEND_ s)
184 prefixOccName prefix (TvOcc s)  = TvOcc (prefix _APPEND_ s)
185 prefixOccName prefix (TCOcc s) = TCOcc (prefix _APPEND_ s)
186
187 -- occNameFlavour is used only to generate good error messages, so it doesn't matter
188 -- that the VarOcc case isn't mega-efficient.  We could have different Occ constructors for
189 -- data constructors and values, but that makes everything else a bit more complicated.
190 occNameFlavour :: OccName -> String
191 occNameFlavour (VarOcc s) | isLexConId s = "Data constructor"
192                           | otherwise    = "Value"
193 occNameFlavour (TvOcc s)  = "Type variable"
194 occNameFlavour (TCOcc s)  = "Type constructor or class"
195
196 isVarOcc, isTCOcc, isTvOcc :: OccName -> Bool
197 isVarOcc (VarOcc s) = True
198 isVarOcc other     = False
199
200 isTvOcc (TvOcc s) = True
201 isTvOcc other     = False
202
203 isTCOcc (TCOcc s) = True
204 isTCOcc other     = False
205
206 instance Eq OccName where
207     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
208     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
209
210 instance Ord OccName where
211     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
212     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
213     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
214     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
215     compare a b = cmpOcc a b
216
217 (VarOcc s1) `cmpOcc` (VarOcc s2) = s1 `compare` s2
218 (VarOcc s1) `cmpOcc` other2      = LT
219
220 (TvOcc s1)  `cmpOcc` (VarOcc s2) = GT
221 (TvOcc s1)  `cmpOcc` (TvOcc s2)  = s1 `compare` s2
222 (TvOcc s1)  `cmpOcc` other       = LT
223
224 (TCOcc s1) `cmpOcc` (TCOcc s2) = s1 `compare` s2
225 (TCOcc s1) `cmpOcc` other      = GT
226
227 instance Outputable OccName where
228   ppr = pprOccName
229 \end{code}
230
231
232 %************************************************************************
233 %*                                                                      *
234 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
235 %*                                                                      *
236 %************************************************************************
237  
238 \begin{code}
239 data Name
240   = Local    Unique
241              (Maybe OccName)    -- For ones that started life with a user name
242
243   | Global   Unique
244              Module             -- The defining module
245              OccName            -- Its name in that module
246              Provenance         -- How it was defined
247 \end{code}
248
249 Things with a @Global@ name are given C static labels, so they finally
250 appear in the .o file's symbol table.  They appear in the symbol table
251 in the form M.n.  If originally-local things have this property they
252 must be made @Global@ first.
253
254 \begin{code}
255 data Provenance
256   = NoProvenance
257
258   | LocalDef                    -- Defined locally
259         SrcLoc                  -- Defn site
260         ExportFlag              -- Whether it's exported
261
262   | NonLocalDef                 -- Defined non-locally
263         SrcLoc                  -- Defined non-locally; src-loc gives defn site
264         IfaceFlavour            -- Whether the defn site is an .hi-boot file
265         PrintUnqualified
266
267   | WiredInTyCon TyCon                  -- There's a wired-in version
268   | WiredInId    Id                     -- ...ditto...
269
270 type PrintUnqualified = Bool    -- True <=> the unqualified name of this thing is
271                                 -- in scope in this module, so print it 
272                                 -- unqualified in error messages
273 \end{code}
274
275 Something is "Exported" if it may be mentioned by another module without
276 warning.  The crucial thing about Exported things is that they must
277 never be dropped as dead code, even if they aren't used in this module.
278 Furthermore, being Exported means that we can't see all call sites of the thing.
279
280 Exported things include:
281
282         - explicitly exported Ids, including data constructors, 
283           class method selectors
284
285         - dfuns from instance decls
286
287 Being Exported is *not* the same as finally appearing in the .o file's 
288 symbol table.  For example, a local Id may be mentioned in an Exported
289 Id's unfolding in the interface file, in which case the local Id goes
290 out too.
291
292 \begin{code}
293 data ExportFlag = Exported  | NotExported
294 \end{code}
295
296 \begin{code}
297 mkLocalName    :: Unique -> OccName -> Name
298 mkLocalName uniq occ = Local uniq (Just occ)
299
300 mkGlobalName :: Unique -> Module -> OccName -> Provenance -> Name
301 mkGlobalName = Global
302
303 mkSysLocalName :: Unique -> Name
304 mkSysLocalName uniq = Local uniq Nothing
305
306 mkWiredInIdName :: Unique -> Module -> FAST_STRING -> Id -> Name
307 mkWiredInIdName uniq mod occ id 
308   = Global uniq mod (VarOcc occ) (WiredInId id)
309
310 mkWiredInTyConName :: Unique -> Module -> FAST_STRING -> TyCon -> Name
311 mkWiredInTyConName uniq mod occ tycon
312   = Global uniq mod (TCOcc occ) (WiredInTyCon tycon)
313
314
315 mkCompoundName :: (OccName -> OccName)
316                -> Unique                -- New unique
317                -> Name                  -- Base name
318                -> Name          -- Result is always a value name
319
320 mkCompoundName f uniq (Global _ mod occ prov)
321   = Global uniq mod (f occ) prov
322
323 mkCompoundName f uniq (Local _ (Just occ))
324   = Local uniq (Just (f occ))
325
326 mkCompoundName f uniq (Local _ Nothing)
327   = Local uniq Nothing
328
329 setNameProvenance :: Name -> Provenance -> Name 
330         -- setNameProvenance used to only change the provenance of 
331         -- Implicit-provenance things, but that gives bad error messages 
332         -- for names defined twice in the same module, so I changed it to 
333         -- set the provenance of *any* global (SLPJ Jun 97)
334 setNameProvenance (Global uniq mod occ _) prov = Global uniq mod occ prov
335 setNameProvenance other_name              prov = other_name
336
337 getNameProvenance :: Name -> Provenance
338 getNameProvenance (Global uniq mod occ prov) = prov
339 getNameProvenance (Local uniq occ)           = LocalDef noSrcLoc NotExported
340
341 -- When we renumber/rename things, we need to be
342 -- able to change a Name's Unique to match the cached
343 -- one in the thing it's the name of.  If you know what I mean.
344 changeUnique (Local      _ n )          u = Local u n
345 changeUnique (Global   _ mod occ  prov) u = Global u mod occ prov
346 \end{code}
347
348 setNameVisibility is applied to names in the final program
349
350 The Maybe Module argument is (Just mod) for top-level values,
351 and Nothing for all others (local values and type variables)
352
353 For top-level things, it globalises Local names 
354                                 (if all top-level things should be visible)
355                          and localises non-exported Global names
356                                  (if only exported things should be visible)
357
358 For nested things it localises Global names.
359
360 In all cases except an exported global, it gives it a new occurrence name.
361
362 The "visibility" here concerns whether the .o file's symbol table
363 mentions the thing; if so, it needs a module name in its symbol.
364 The Global things are "visible" and the Local ones are not
365
366 Why should things be "visible"?  Certainly they must be if they
367 are exported.  But also:
368
369 (a) In certain (prelude only) modules we split up the .hc file into
370     lots of separate little files, which are separately compiled by the C
371     compiler.  That gives lots of little .o files.  The idea is that if
372     you happen to mention one of them you don't necessarily pull them all
373     in.  (Pulling in a piece you don't need can be v bad, because it may
374     mention other pieces you don't need either, and so on.)
375     
376     Sadly, splitting up .hc files means that local names (like s234) are
377     now globally visible, which can lead to clashes between two .hc
378     files. So unlocaliseWhatnot goes through making all the local things
379     into global things, essentially by giving them full names so when they
380     are printed they'll have their module name too.  Pretty revolting
381     really.
382
383 (b) When optimisation is on we want to make all the internal
384     top-level defns externally visible
385
386 \begin{code}
387 setNameVisibility :: Maybe Module -> Unique -> Name -> Name
388
389 setNameVisibility maybe_mod uniq name@(Global _ mod occ (LocalDef loc NotExported))
390   | not all_toplev_ids_visible || not_top_level maybe_mod
391   = Local uniq Nothing                          -- Localise Global name
392
393 setNameVisibility maybe_mod uniq name@(Global _ _ _ _)
394   = name                                        -- Otherwise don't fiddle with Global
395
396 setNameVisibility (Just mod) uniq (Local _ _)
397   | all_toplev_ids_visible
398   = Global uniq mod                             -- Globalise Local name
399            (uniqToOccName uniq)
400            (LocalDef noSrcLoc NotExported)
401
402 setNameVisibility maybe_mod uniq (Local _ _)
403   = Local uniq Nothing                  -- New unique for Local; zap its occ
404
405 -- make the Name globally visible regardless.
406 mkNameVisible :: Module -> Unique -> Name -> Name
407 mkNameVisible mod occ_uniq nm@(Global _ _ _ _) = nm
408 mkNameVisible mod occ_uniq nm@(Local uniq occ)
409  = Global uniq mod (uniqToOccName occ_uniq) (LocalDef noSrcLoc Exported)
410
411 uniqToOccName uniq = VarOcc (_PK_ ('_':show uniq))
412         -- The "_" is to make sure that this OccName is distinct from all user-defined ones
413
414 not_top_level (Just m) = False
415 not_top_level Nothing  = True
416
417 all_toplev_ids_visible = 
418         not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
419         opt_EnsureSplittableC            -- Splitting requires visiblilty
420 \end{code}
421
422 %************************************************************************
423 %*                                                                      *
424 \subsection{Predicates and selectors}
425 %*                                                                      *
426 %************************************************************************
427
428 \begin{code}
429 nameUnique              :: Name -> Unique
430 nameModAndOcc           :: Name -> (Module, OccName)    -- Globals only
431 nameOccName             :: Name -> OccName 
432 nameModule              :: Name -> Module
433 nameSrcLoc              :: Name -> SrcLoc
434 isLocallyDefinedName    :: Name -> Bool
435 isExportedName          :: Name -> Bool
436 isWiredInName           :: Name -> Bool
437 isLocalName             :: Name -> Bool
438 isGlobalName            :: Name -> Bool
439 isExternallyVisibleName :: Name -> Bool
440
441
442
443 nameUnique (Local  u _)     = u
444 nameUnique (Global u _ _ _) = u
445
446 nameOccName (Local _ (Just occ)) = occ
447 nameOccName (Local uniq Nothing) = pprPanic "nameOccName" (ppr uniq)
448 nameOccName (Global _ _ occ _)   = occ
449
450 nameModule (Global _ mod occ _) = mod
451
452 nameModAndOcc (Global _ mod occ _) = (mod,occ)
453
454 isExportedName (Global _ _ _ (LocalDef _ Exported)) = True
455 isExportedName other                                = False
456
457 nameSrcLoc (Local _ _)                          = noSrcLoc
458 nameSrcLoc (Global _ _ _ (LocalDef loc _))      = loc
459 nameSrcLoc (Global _ _ _ (NonLocalDef loc _ _)) = loc
460 nameSrcLoc (Global _ _ _ (WiredInTyCon _))      = mkBuiltinSrcLoc
461 nameSrcLoc (Global _ _ _ (WiredInId _))         = mkBuiltinSrcLoc
462 nameSrcLoc other                                = noSrcLoc
463   
464 isLocallyDefinedName (Local  _ _)                  = True
465 isLocallyDefinedName (Global _ _ _ (LocalDef _ _)) = True
466 isLocallyDefinedName other                         = False
467
468 -- Things the compiler "knows about" are in some sense
469 -- "imported".  When we are compiling the module where
470 -- the entities are defined, we need to be able to pick
471 -- them out, often in combination with isLocallyDefined.
472 isWiredInName (Global _ _ _ (WiredInTyCon _)) = True
473 isWiredInName (Global _ _ _ (WiredInId    _)) = True
474 isWiredInName _                               = False
475
476 maybeWiredInIdName :: Name -> Maybe Id
477 maybeWiredInIdName (Global _ _ _ (WiredInId id)) = Just id
478 maybeWiredInIdName other                         = Nothing
479
480 maybeWiredInTyConName :: Name -> Maybe TyCon
481 maybeWiredInTyConName (Global _ _ _ (WiredInTyCon tc)) = Just tc
482 maybeWiredInTyConName other                            = Nothing
483
484
485 isLocalName (Local _ _) = True
486 isLocalName _           = False
487
488 isSysLocalName (Local _ Nothing) = True
489 isSysLocalName other             = False
490
491 isGlobalName (Global _ _ _ _) = True
492 isGlobalName other            = False
493
494 -- Global names are by definition those that are visible
495 -- outside the module, *as seen by the linker*.  Externally visible
496 -- does not mean visible at the source level (that's isExported).
497 isExternallyVisibleName name = isGlobalName name
498 \end{code}
499
500
501 %************************************************************************
502 %*                                                                      *
503 \subsection[Name-instances]{Instance declarations}
504 %*                                                                      *
505 %************************************************************************
506
507 \begin{code}
508 cmpName n1 n2 = c n1 n2
509   where
510     c (Local  u1 _)   (Local  u2 _)       = compare u1 u2
511     c (Local   _ _)       _               = LT
512     c (Global u1 _ _ _) (Global u2 _ _ _) = compare u1 u2
513     c (Global  _ _ _ _)   _               = GT
514 \end{code}
515
516 \begin{code}
517 instance Eq Name where
518     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
519     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
520
521 instance Ord Name where
522     a <= b = case (a `compare` b) of { LT -> True;      EQ -> True;  GT -> False }
523     a <  b = case (a `compare` b) of { LT -> True;      EQ -> False; GT -> False }
524     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
525     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
526     compare a b = cmpName a b
527
528 instance Uniquable Name where
529     getUnique = nameUnique
530
531 instance NamedThing Name where
532     getName n = n
533 \end{code}
534
535
536 %************************************************************************
537 %*                                                                      *
538 \subsection[Special-Names]{Special Kinds of names}
539 %*                                                                      *
540 %************************************************************************
541
542 Here's our convention for splitting up the object file name space:
543
544         _d...           dictionary identifiers
545         _g...           externally visible (non-user visible) names
546
547         _m...           default methods
548         _n...           default methods (encoded symbols, eg. <= becomes _nle)
549
550         _p...           superclass selectors
551
552         _w...           workers
553         _v...           workers (encoded symbols)
554
555         _x...           local variables
556
557         _u...           user-defined names that previously began with '_'
558
559         _[A-Z]...       compiler-generated tycons/datacons (namely dictionary
560                         constructors)
561
562         __....          keywords (__export, __letrec etc.)
563
564 This knowledge is encoded in the following functions.
565
566 \begin{code}
567 dictNamePrefix :: FAST_STRING
568 dictNamePrefix  = SLIT("_d")
569
570 mkSuperDictSelName :: Int -> OccName -> OccName
571 mkSuperDictSelName index = prefixOccName (_PK_ ("_p" ++ show index ++ "_"))
572
573 mkWorkerName :: OccName -> OccName
574 mkWorkerName nm
575   | isLexSym nm_str = 
576         prefixOccName SLIT("_v") (mapOccName trName nm)
577   | otherwise                = 
578         prefixOccName SLIT("_w") nm
579   where nm_str = occNameString nm
580
581 mkDefaultMethodName :: OccName -> OccName
582 mkDefaultMethodName nm
583   | isLexSym nm_str = 
584         prefixOccName SLIT("_n") (mapOccName trName nm)
585   | otherwise                = 
586         prefixOccName SLIT("_m") nm
587   where nm_str = occNameString nm
588
589 -- not used yet:
590 --mkRecordSelectorName     :: Name -> Name
591 --mkMethodSelectorName     :: Name -> Name
592
593 mkClassTyConStr, mkClassDataConStr :: FAST_STRING -> FAST_STRING
594
595 mkClassTyConStr   s = SLIT("_") _APPEND_ s
596 mkClassDataConStr s = SLIT("_") _APPEND_ s
597
598 -- translate a string such that it can occur as *part* of an identifer.  This
599 -- is used when we prefix identifiers to create new names, for example the
600 -- name of a default method.
601
602 trName :: FAST_STRING -> FAST_STRING
603 trName nm = _PK_ (foldr tran "" (_UNPK_ nm))
604  where 
605     tran c cs = case trChar c of
606                    '\0' -> '_' : show (ord c) ++ cs
607                    c'   -> c' : cs
608     trChar '&'  = 'a'
609     trChar '|'  = 'b'
610     trChar ':'  = 'c'
611     trChar '/'  = 'd'
612     trChar '='  = 'e'
613     trChar '>'  = 'g'
614     trChar '#'  = 'h'
615     trChar '@'  = 'i'
616     trChar '<'  = 'l'
617     trChar '-'  = 'm'
618     trChar '!'  = 'n'
619     trChar '+'  = 'p'
620     trChar '\'' = 'q'
621     trChar '$'  = 'r'
622     trChar '?'  = 's'
623     trChar '*'  = 't'
624     trChar '_'  = 'u'
625     trChar '.'  = 'v'
626     trChar '\\' = 'w'
627     trChar '%'  = 'x'
628     trChar '~'  = 'y'
629     trChar '^'  = 'z'
630     trChar _    = '\0'
631 \end{code}
632
633 %************************************************************************
634 %*                                                                      *
635 \subsection{Pretty printing}
636 %*                                                                      *
637 %************************************************************************
638
639 \begin{code}
640 instance Outputable Name where
641         -- When printing interfaces, all Locals have been given nice print-names
642     ppr name = pprName name
643
644 pprName name
645   = getPprStyle $ \ sty ->
646     let
647        -- when printing local names for interface files, prepend the '_'
648        -- to avoid clashes with user-defined names.  In fact, these names
649        -- will always begin with 'g' for top-level ids and 'x' otherwise,
650        -- because these are the unique supplies going into the tidy phase.
651        ppr (Local u n) | codeStyle sty   = pprUnique u
652                        | ifaceStyle sty  = char '_' <> pprUnique u
653
654        ppr (Local u Nothing)    = pprUnique u
655        ppr (Local u (Just occ)) | userStyle sty = ptext (occNameString occ)
656                                 | otherwise     = ptext (occNameString occ) <> char '_' <> pprUnique u
657    
658        ppr name@(Global u m n prov)
659          | codeStyle sty
660          = identToC (m _APPEND_ SLIT(".") _APPEND_ occNameString n)
661    
662          | otherwise  
663          = hcat [pp_mod_dot, ptext (occNameString n), pp_debug sty name]
664          where
665            pp_mod_dot 
666              = case prov of   -- Omit home module qualifier if in scope 
667                    LocalDef _ _          -> pp_qual dot (user_sty || iface_sty)
668                    NonLocalDef _ hif omit -> pp_qual (pp_hif hif) (omit && user_sty)
669                                  -- Hack: omit qualifers on wired in things
670                                  -- in user style only
671                    WiredInTyCon _       -> pp_qual dot user_sty
672                    WiredInId _          -> pp_qual dot user_sty
673                    NoProvenance         -> pp_qual dot False
674    
675            pp_qual sep omit_qual
676             | omit_qual  = empty
677             | otherwise  = pprModule m <> sep
678
679            dot = text "."
680            pp_hif HiFile     = dot       -- Vanilla case
681            pp_hif HiBootFile = text "!"  -- M!t indicates a name imported from a .hi-boot interface
682
683            user_sty  = userStyle sty
684            iface_sty = ifaceStyle sty
685     in
686     ppr name
687    
688    
689 pp_debug sty (Global uniq m n prov) 
690   | debugStyle sty = hcat [text "{-", pprUnique uniq, prov_p, text "-}"]
691   | otherwise      = empty
692                    where
693                      prov_p | opt_PprStyle_NoPrags = empty
694                             | otherwise            = comma <> pp_prov prov
695
696 pp_prov (LocalDef _ Exported)    = char 'x'
697 pp_prov (LocalDef _ NotExported) = char 'l'
698 pp_prov (NonLocalDef _ _ _)      = char 'n'
699 pp_prov (WiredInTyCon _)         = char 'W'
700 pp_prov (WiredInId _)            = char 'w'
701 pp_prov NoProvenance             = char '?'
702
703 -- pprNameProvenance is used in error messages to say where a name came from
704 pprNameProvenance :: Name -> SDoc
705 pprNameProvenance (Local _ _)         = pprProvenance (LocalDef noSrcLoc NotExported)
706 pprNameProvenance (Global _ _ _ prov) = pprProvenance prov
707
708 pprProvenance :: Provenance -> SDoc
709 pprProvenance (LocalDef loc _)      = ptext SLIT("Locally defined at")     <+> ppr loc
710 pprProvenance (NonLocalDef loc _ _) = ptext SLIT("Non-locally defined at") <+> ppr loc
711 pprProvenance (WiredInTyCon tc)     = ptext SLIT("Wired-in tycon")
712 pprProvenance (WiredInId id)        = ptext SLIT("Wired-in id")
713 pprProvenance NoProvenance          = ptext SLIT("No provenance")
714 \end{code}
715
716
717 %************************************************************************
718 %*                                                                      *
719 \subsection{Overloaded functions related to Names}
720 %*                                                                      *
721 %************************************************************************
722
723 \begin{code}
724 class NamedThing a where
725     getOccName :: a -> OccName          -- Even RdrNames can do this!
726     getName    :: a -> Name
727
728     getOccName n = nameOccName (getName n)      -- Default method
729 \end{code}
730
731 \begin{code}
732 modAndOcc           :: NamedThing a => a -> (Module, OccName)
733 getSrcLoc           :: NamedThing a => a -> SrcLoc
734 isLocallyDefined    :: NamedThing a => a -> Bool
735 isExported          :: NamedThing a => a -> Bool
736 getOccString        :: NamedThing a => a -> String
737
738 modAndOcc           = nameModAndOcc        . getName
739 isExported          = isExportedName       . getName
740 getSrcLoc           = nameSrcLoc           . getName
741 isLocallyDefined    = isLocallyDefinedName . getName
742 getOccString x      = _UNPK_ (occNameString (getOccName x))
743 \end{code}
744
745 \begin{code}
746 {-# SPECIALIZE isLocallyDefined
747         :: Name     -> Bool
748   #-}
749 \end{code}