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