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