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