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