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