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