Improve printing of Orig RdrNames
[ghc-hetmet.git] / compiler / basicTypes / Name.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[Name]{@Name@: to transmit name info from renamer to typechecker}
6
7 \begin{code}
8 -- |
9 -- #name_types#
10 -- GHC uses several kinds of name internally:
11 --
12 -- * 'OccName.OccName': see "OccName#name_types"
13 --
14 -- * 'RdrName.RdrName': see "RdrName#name_types"
15 --
16 -- *  'Name.Name' is the type of names that have had their scoping and binding resolved. They
17 --   have an 'OccName.OccName' but also a 'Unique.Unique' that disambiguates Names that have
18 --   the same 'OccName.OccName' and indeed is used for all 'Name.Name' comparison. Names
19 --   also contain information about where they originated from, see "Name#name_sorts"
20 --
21 -- * 'Id.Id': see "Id#name_types"
22 --
23 -- * 'Var.Var': see "Var#name_types"
24 --
25 -- #name_sorts#
26 -- Names are one of:
27 --
28 --  * External, if they name things declared in other modules. Some external
29 --    Names are wired in, i.e. they name primitives defined in the compiler itself
30 --
31 --  * Internal, if they name things in the module being compiled. Some internal
32 --    Names are system names, if they are names manufactured by the compiler
33
34 module Name (
35         -- * The main types
36         Name,                                   -- Abstract
37         BuiltInSyntax(..),
38
39         -- ** Creating 'Name's
40         mkInternalName, mkSystemName,
41         mkSystemVarName, mkSysTvName, 
42         mkFCallName, mkIPName,
43         mkTickBoxOpName,
44         mkExternalName, mkWiredInName,
45
46         -- ** Manipulating and deconstructing 'Name's
47         nameUnique, setNameUnique,
48         nameOccName, nameModule, nameModule_maybe,
49         tidyNameOcc, 
50         hashName, localiseName,
51
52         nameSrcLoc, nameSrcSpan, pprNameLoc,
53
54         -- ** Predicates on 'Name's
55         isSystemName, isInternalName, isExternalName,
56         isTyVarName, isTyConName, isDataConName, 
57         isValName, isVarName,
58         isWiredInName, isBuiltInSyntax,
59         wiredInNameTyThing_maybe, 
60         nameIsLocalOrFrom,
61
62         -- * Class 'NamedThing' and overloaded friends
63         NamedThing(..),
64         getSrcLoc, getSrcSpan, getOccString,
65
66         pprInfixName, pprPrefixName, pprModulePrefix,
67
68         -- Re-export the OccName stuff
69         module OccName
70     ) where
71
72 import {-# SOURCE #-} TypeRep( TyThing )
73
74 import OccName
75 import Module
76 import SrcLoc
77 import Unique
78 import Maybes
79 import Binary
80 import StaticFlags
81 import FastTypes
82 import FastString
83 import Outputable
84
85 import Data.Array
86 \end{code}
87
88 %************************************************************************
89 %*                                                                      *
90 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
91 %*                                                                      *
92 %************************************************************************
93  
94 \begin{code}
95 -- | A unique, unambigious name for something, containing information about where
96 -- that thing originated.
97 data Name = Name {
98                 n_sort :: NameSort,     -- What sort of name it is
99                 n_occ  :: !OccName,     -- Its occurrence name
100                 n_uniq :: FastInt,      -- UNPACK doesn't work, recursive type
101 --(note later when changing Int# -> FastInt: is that still true about UNPACK?)
102                 n_loc  :: !SrcSpan      -- Definition site
103             }
104
105 -- NOTE: we make the n_loc field strict to eliminate some potential
106 -- (and real!) space leaks, due to the fact that we don't look at
107 -- the SrcLoc in a Name all that often.
108
109 data NameSort
110   = External Module
111  
112   | WiredIn Module TyThing BuiltInSyntax
113         -- A variant of External, for wired-in things
114
115   | Internal            -- A user-defined Id or TyVar
116                         -- defined in the module being compiled
117
118   | System              -- A system-defined Id or TyVar.  Typically the
119                         -- OccName is very uninformative (like 's')
120
121 -- | BuiltInSyntax is for things like @(:)@, @[]@ and tuples, 
122 -- which have special syntactic forms.  They aren't in scope
123 -- as such.
124 data BuiltInSyntax = BuiltInSyntax | UserSyntax
125 \end{code}
126
127 Notes about the NameSorts:
128
129 1.  Initially, top-level Ids (including locally-defined ones) get External names, 
130     and all other local Ids get Internal names
131
132 2.  Things with a External name are given C static labels, so they finally
133     appear in the .o file's symbol table.  They appear in the symbol table
134     in the form M.n.  If originally-local things have this property they
135     must be made @External@ first.
136
137 3.  In the tidy-core phase, a External that is not visible to an importer
138     is changed to Internal, and a Internal that is visible is changed to External
139
140 4.  A System Name differs in the following ways:
141         a) has unique attached when printing dumps
142         b) unifier eliminates sys tyvars in favour of user provs where possible
143
144     Before anything gets printed in interface files or output code, it's
145     fed through a 'tidy' processor, which zaps the OccNames to have
146     unique names; and converts all sys-locals to user locals
147     If any desugarer sys-locals have survived that far, they get changed to
148     "ds1", "ds2", etc.
149
150 Built-in syntax => It's a syntactic form, not "in scope" (e.g. [])
151
152 Wired-in thing  => The thing (Id, TyCon) is fully known to the compiler, 
153                    not read from an interface file. 
154                    E.g. Bool, True, Int, Float, and many others
155
156 All built-in syntax is for wired-in things.
157
158 \begin{code}
159 nameUnique              :: Name -> Unique
160 nameOccName             :: Name -> OccName 
161 nameModule              :: Name -> Module
162 nameSrcLoc              :: Name -> SrcLoc
163 nameSrcSpan             :: Name -> SrcSpan
164
165 nameUnique  name = mkUniqueGrimily (iBox (n_uniq name))
166 nameOccName name = n_occ  name
167 nameSrcLoc  name = srcSpanStart (n_loc name)
168 nameSrcSpan name = n_loc  name
169 \end{code}
170
171 %************************************************************************
172 %*                                                                      *
173 \subsection{Predicates on names}
174 %*                                                                      *
175 %************************************************************************
176
177 \begin{code}
178 nameIsLocalOrFrom :: Module -> Name -> Bool
179 isInternalName    :: Name -> Bool
180 isExternalName    :: Name -> Bool
181 isSystemName      :: Name -> Bool
182 isWiredInName     :: Name -> Bool
183
184 isWiredInName (Name {n_sort = WiredIn _ _ _}) = True
185 isWiredInName _                               = False
186
187 wiredInNameTyThing_maybe :: Name -> Maybe TyThing
188 wiredInNameTyThing_maybe (Name {n_sort = WiredIn _ thing _}) = Just thing
189 wiredInNameTyThing_maybe _                                   = Nothing
190
191 isBuiltInSyntax :: Name -> Bool
192 isBuiltInSyntax (Name {n_sort = WiredIn _ _ BuiltInSyntax}) = True
193 isBuiltInSyntax _                                           = False
194
195 isExternalName (Name {n_sort = External _})    = True
196 isExternalName (Name {n_sort = WiredIn _ _ _}) = True
197 isExternalName _                               = False
198
199 isInternalName name = not (isExternalName name)
200
201 nameModule name = nameModule_maybe name `orElse` pprPanic "nameModule" (ppr name)
202 nameModule_maybe :: Name -> Maybe Module
203 nameModule_maybe (Name { n_sort = External mod})    = Just mod
204 nameModule_maybe (Name { n_sort = WiredIn mod _ _}) = Just mod
205 nameModule_maybe _                                  = Nothing
206
207 nameIsLocalOrFrom from name
208   | isExternalName name = from == nameModule name
209   | otherwise           = True
210
211 isTyVarName :: Name -> Bool
212 isTyVarName name = isTvOcc (nameOccName name)
213
214 isTyConName :: Name -> Bool
215 isTyConName name = isTcOcc (nameOccName name)
216
217 isDataConName :: Name -> Bool
218 isDataConName name = isDataOcc (nameOccName name)
219
220 isValName :: Name -> Bool
221 isValName name = isValOcc (nameOccName name)
222
223 isVarName :: Name -> Bool
224 isVarName = isVarOcc . nameOccName
225
226 isSystemName (Name {n_sort = System}) = True
227 isSystemName _                        = False
228 \end{code}
229
230
231 %************************************************************************
232 %*                                                                      *
233 \subsection{Making names}
234 %*                                                                      *
235 %************************************************************************
236
237 \begin{code}
238 -- | Create a name which is (for now at least) local to the current module and hence
239 -- does not need a 'Module' to disambiguate it from other 'Name's
240 mkInternalName :: Unique -> OccName -> SrcSpan -> Name
241 mkInternalName uniq occ loc = Name { n_uniq = getKeyFastInt uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
242         -- NB: You might worry that after lots of huffing and
243         -- puffing we might end up with two local names with distinct
244         -- uniques, but the same OccName.  Indeed we can, but that's ok
245         --      * the insides of the compiler don't care: they use the Unique
246         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
247         --        uniques if you get confused
248         --      * for interface files we tidyCore first, which puts the uniques
249         --        into the print name (see setNameVisibility below)
250
251 -- | Create a name which definitely originates in the given module
252 mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
253 mkExternalName uniq mod occ loc 
254   = Name { n_uniq = getKeyFastInt uniq, n_sort = External mod,
255            n_occ = occ, n_loc = loc }
256
257 -- | Create a name which is actually defined by the compiler itself
258 mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
259 mkWiredInName mod occ uniq thing built_in
260   = Name { n_uniq = getKeyFastInt uniq,
261            n_sort = WiredIn mod thing built_in,
262            n_occ = occ, n_loc = wiredInSrcSpan }
263
264 -- | Create a name brought into being by the compiler
265 mkSystemName :: Unique -> OccName -> Name
266 mkSystemName uniq occ = Name { n_uniq = getKeyFastInt uniq, n_sort = System, 
267                                n_occ = occ, n_loc = noSrcSpan }
268
269 mkSystemVarName :: Unique -> FastString -> Name
270 mkSystemVarName uniq fs = mkSystemName uniq (mkVarOccFS fs)
271
272 mkSysTvName :: Unique -> FastString -> Name
273 mkSysTvName uniq fs = mkSystemName uniq (mkOccNameFS tvName fs) 
274
275 -- | Make a name for a foreign call
276 mkFCallName :: Unique -> String -> Name
277         -- The encoded string completely describes the ccall
278 mkFCallName uniq str =  Name { n_uniq = getKeyFastInt uniq, n_sort = Internal, 
279                                n_occ = mkVarOcc str, n_loc = noSrcSpan }
280
281
282 mkTickBoxOpName :: Unique -> String -> Name
283 mkTickBoxOpName uniq str 
284    = Name { n_uniq = getKeyFastInt uniq, n_sort = Internal, 
285             n_occ = mkVarOcc str, n_loc = noSrcSpan }
286
287 -- | Make the name of an implicit parameter
288 mkIPName :: Unique -> OccName -> Name
289 mkIPName uniq occ
290   = Name { n_uniq = getKeyFastInt uniq,
291            n_sort = Internal,
292            n_occ  = occ,
293            n_loc = noSrcSpan }
294 \end{code}
295
296 \begin{code}
297 -- When we renumber/rename things, we need to be
298 -- able to change a Name's Unique to match the cached
299 -- one in the thing it's the name of.  If you know what I mean.
300 setNameUnique :: Name -> Unique -> Name
301 setNameUnique name uniq = name {n_uniq = getKeyFastInt uniq}
302
303 tidyNameOcc :: Name -> OccName -> Name
304 -- We set the OccName of a Name when tidying
305 -- In doing so, we change System --> Internal, so that when we print
306 -- it we don't get the unique by default.  It's tidy now!
307 tidyNameOcc name@(Name { n_sort = System }) occ = name { n_occ = occ, n_sort = Internal}
308 tidyNameOcc name                            occ = name { n_occ = occ }
309
310 -- | Make the 'Name' into an internal name, regardless of what it was to begin with
311 localiseName :: Name -> Name
312 localiseName n = n { n_sort = Internal }
313 \end{code}
314
315 %************************************************************************
316 %*                                                                      *
317 \subsection{Hashing and comparison}
318 %*                                                                      *
319 %************************************************************************
320
321 \begin{code}
322 hashName :: Name -> Int         -- ToDo: should really be Word
323 hashName name = getKey (nameUnique name) + 1
324         -- The +1 avoids keys with lots of zeros in the ls bits, which 
325         -- interacts badly with the cheap and cheerful multiplication in
326         -- hashExpr
327
328 cmpName :: Name -> Name -> Ordering
329 cmpName n1 n2 = iBox (n_uniq n1) `compare` iBox (n_uniq n2)
330 \end{code}
331
332 %************************************************************************
333 %*                                                                      *
334 \subsection[Name-instances]{Instance declarations}
335 %*                                                                      *
336 %************************************************************************
337
338 \begin{code}
339 instance Eq Name where
340     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
341     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
342
343 instance Ord Name where
344     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
345     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
346     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
347     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
348     compare a b = cmpName a b
349
350 instance Uniquable Name where
351     getUnique = nameUnique
352
353 instance NamedThing Name where
354     getName n = n
355 \end{code}
356
357 %************************************************************************
358 %*                                                                      *
359 \subsection{Binary}
360 %*                                                                      *
361 %************************************************************************
362
363 \begin{code}
364 instance Binary Name where
365    put_ bh name =
366       case getUserData bh of 
367         UserData{ ud_put_name = put_name } -> put_name bh name
368
369    get bh = do
370         i <- get bh
371         return $! (ud_symtab (getUserData bh) ! i)
372 \end{code}
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection{Pretty printing}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381 instance Outputable Name where
382     ppr name = pprName name
383
384 instance OutputableBndr Name where
385     pprBndr _ name = pprName name
386
387 pprName :: Name -> SDoc
388 pprName (Name {n_sort = sort, n_uniq = u, n_occ = occ})
389   = getPprStyle $ \ sty ->
390     case sort of
391       WiredIn mod _ builtin   -> pprExternal sty uniq mod occ True  builtin
392       External mod            -> pprExternal sty uniq mod occ False UserSyntax
393       System                  -> pprSystem sty uniq occ
394       Internal                -> pprInternal sty uniq occ
395   where uniq = mkUniqueGrimily (iBox u)
396
397 pprExternal :: PprStyle -> Unique -> Module -> OccName -> Bool -> BuiltInSyntax -> SDoc
398 pprExternal sty uniq mod occ is_wired is_builtin
399   | codeStyle sty = ppr mod <> char '_' <> ppr_z_occ_name occ
400         -- In code style, always qualify
401         -- ToDo: maybe we could print all wired-in things unqualified
402         --       in code style, to reduce symbol table bloat?
403   | debugStyle sty = ppr mod <> dot <> ppr_occ_name occ
404                      <> braces (hsep [if is_wired then ptext (sLit "(w)") else empty,
405                                       pprNameSpaceBrief (occNameSpace occ), 
406                                       pprUnique uniq])
407   | BuiltInSyntax <- is_builtin = ppr_occ_name occ  -- Never qualify builtin syntax
408   | otherwise                   = pprModulePrefix sty mod occ <> ppr_occ_name occ
409
410 pprInternal :: PprStyle -> Unique -> OccName -> SDoc
411 pprInternal sty uniq occ
412   | codeStyle sty  = pprUnique uniq
413   | debugStyle sty = ppr_occ_name occ <> braces (hsep [pprNameSpaceBrief (occNameSpace occ), 
414                                                        pprUnique uniq])
415   | dumpStyle sty  = ppr_occ_name occ <> ppr_underscore_unique uniq
416                         -- For debug dumps, we're not necessarily dumping
417                         -- tidied code, so we need to print the uniques.
418   | otherwise      = ppr_occ_name occ   -- User style
419
420 -- Like Internal, except that we only omit the unique in Iface style
421 pprSystem :: PprStyle -> Unique -> OccName -> SDoc
422 pprSystem sty uniq occ
423   | codeStyle sty  = pprUnique uniq
424   | debugStyle sty = ppr_occ_name occ <> ppr_underscore_unique uniq
425                      <> braces (pprNameSpaceBrief (occNameSpace occ))
426   | otherwise      = ppr_occ_name occ <> ppr_underscore_unique uniq
427                                 -- If the tidy phase hasn't run, the OccName
428                                 -- is unlikely to be informative (like 's'),
429                                 -- so print the unique
430
431
432 pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
433 -- Print the "M." part of a name, based on whether it's in scope or not
434 -- See Note [Printing original names] in HscTypes
435 pprModulePrefix sty mod occ
436   = case qualName sty mod occ of                   -- See Outputable.QualifyName:
437       NameQual modname -> ppr modname <> dot       -- Name is in scope       
438       NameNotInScope1  -> ppr mod <> dot           -- Not in scope
439       NameNotInScope2  -> ppr (modulePackageId mod) <> colon     -- Module not in
440                           <> ppr (moduleName mod) <> dot         -- scope eithber
441       _otherwise       -> empty
442
443 ppr_underscore_unique :: Unique -> SDoc
444 -- Print an underscore separating the name from its unique
445 -- But suppress it if we aren't printing the uniques anyway
446 ppr_underscore_unique uniq
447   | opt_SuppressUniques = empty
448   | otherwise           = char '_' <> pprUnique uniq
449
450 ppr_occ_name :: OccName -> SDoc
451 ppr_occ_name occ = ftext (occNameFS occ)
452         -- Don't use pprOccName; instead, just print the string of the OccName; 
453         -- we print the namespace in the debug stuff above
454
455 -- In code style, we Z-encode the strings.  The results of Z-encoding each FastString are
456 -- cached behind the scenes in the FastString implementation.
457 ppr_z_occ_name :: OccName -> SDoc
458 ppr_z_occ_name occ = ftext (zEncodeFS (occNameFS occ))
459
460 -- Prints (if mod information is available) "Defined at <loc>" or 
461 --  "Defined in <mod>" information for a Name.
462 pprNameLoc :: Name -> SDoc
463 pprNameLoc name
464   | isGoodSrcSpan loc = pprDefnLoc loc
465   | isInternalName name || isSystemName name 
466                       = ptext (sLit "<no location info>")
467   | otherwise         = ptext (sLit "Defined in ") <> ppr (nameModule name)
468   where loc = nameSrcSpan name
469 \end{code}
470
471 %************************************************************************
472 %*                                                                      *
473 \subsection{Overloaded functions related to Names}
474 %*                                                                      *
475 %************************************************************************
476
477 \begin{code}
478 -- | A class allowing convenient access to the 'Name' of various datatypes
479 class NamedThing a where
480     getOccName :: a -> OccName
481     getName    :: a -> Name
482
483     getOccName n = nameOccName (getName n)      -- Default method
484 \end{code}
485
486 \begin{code}
487 getSrcLoc           :: NamedThing a => a -> SrcLoc
488 getSrcSpan          :: NamedThing a => a -> SrcSpan
489 getOccString        :: NamedThing a => a -> String
490
491 getSrcLoc           = nameSrcLoc           . getName
492 getSrcSpan          = nameSrcSpan          . getName
493 getOccString        = occNameString        . getOccName
494
495 pprInfixName, pprPrefixName :: (Outputable a, NamedThing a) => a -> SDoc
496 -- See Outputable.pprPrefixVar, pprInfixVar; 
497 -- add parens or back-quotes as appropriate
498 pprInfixName  n = pprInfixVar  (isSymOcc (getOccName n)) (ppr n)
499 pprPrefixName n = pprPrefixVar (isSymOcc (getOccName n)) (ppr n)
500 \end{code}
501