[project @ 2000-10-30 09:52:14 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Name.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Name]{@Name@: to transmit name info from renamer to typechecker}
5
6 \begin{code}
7 module Name (
8         -- Re-export the OccName stuff
9         module OccName,
10
11         -- The Name type
12         Name,                                   -- Abstract
13         mkLocalName, mkImportedLocalName, mkSysLocalName, mkCCallName,
14         mkTopName, mkIPName,
15         mkDerivedName, mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
16
17         nameUnique, setNameUnique, setLocalNameSort,
18         tidyTopName, 
19         nameOccName, nameModule, nameModule_maybe,
20         setNameOcc, nameRdrName, setNameModuleAndLoc, 
21         toRdrName, hashName,
22
23         isUserExportedName,
24         nameSrcLoc, isLocallyDefinedName, isDllName,
25
26         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
27         isTyVarName,
28         
29         -- Environment
30         NameEnv, mkNameEnv,
31         emptyNameEnv, unitNameEnv, nameEnvElts, 
32         extendNameEnv_C, extendNameEnv, 
33         plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList,
34         lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, 
35
36
37         -- Class NamedThing and overloaded friends
38         NamedThing(..),
39         getSrcLoc, isLocallyDefined, getOccString, toRdrName
40     ) where
41
42 #include "HsVersions.h"
43
44 import OccName          -- All of it
45 import Module           ( Module, moduleName, mkVanillaModule, 
46                           printModulePrefix, isModuleInThisPackage )
47 import RdrName          ( RdrName, mkRdrQual, mkRdrUnqual, rdrNameOcc, rdrNameModule )
48 import CmdLineOpts      ( opt_Static, opt_OmitInterfacePragmas, opt_EnsureSplittableC )
49 import SrcLoc           ( builtinSrcLoc, noSrcLoc, SrcLoc )
50 import Unique           ( Unique, Uniquable(..), u2i, pprUnique, pprUnique10 )
51 import Maybes           ( expectJust )
52 import FastTypes
53 import UniqFM
54 import Outputable
55 \end{code}
56
57 %************************************************************************
58 %*                                                                      *
59 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
60 %*                                                                      *
61 %************************************************************************
62  
63 \begin{code}
64 data Name = Name {
65                 n_sort :: NameSort,     -- What sort of name it is
66                 n_occ  :: OccName,      -- Its occurrence name
67                 n_uniq :: Unique,
68                 n_loc  :: SrcLoc        -- Definition site
69             }
70
71 data NameSort
72   = Global Module       -- (a) TyCon, Class, their derived Ids, dfun Id
73                         -- (b) imported Id
74
75   | Exported            -- An exported Ids defined in the module being compiled
76
77   | Local               -- A user-defined, but non-exported Id or TyVar,
78                         -- defined in the module being compiled
79
80   | System              -- A system-defined Id or TyVar.  Typically the
81                         -- OccName is very uninformative (like 's')
82 \end{code}
83
84 Notes about the NameSorts:
85
86 1.  An Exported Id is changed to Global right at the
87     end in the tidyCore pass, so that an importer sees a Global
88     Similarly, Local Ids that are visible to an importer (e.g. when 
89     optimisation is on) are changed to Globals.
90
91 2.  Things with a @Global@ name are given C static labels, so they finally
92     appear in the .o file's symbol table.  They appear in the symbol table
93     in the form M.n.  If originally-local things have this property they
94     must be made @Global@ first.
95
96 3.  A System Name differs in the following ways:
97         a) has unique attached when printing dumps
98         b) unifier eliminates sys tyvars in favour of user provs where possible
99
100     Before anything gets printed in interface files or output code, it's
101     fed through a 'tidy' processor, which zaps the OccNames to have
102     unique names; and converts all sys-locals to user locals
103     If any desugarer sys-locals have survived that far, they get changed to
104     "ds1", "ds2", etc.
105
106 \begin{code}
107 nameUnique              :: Name -> Unique
108 nameOccName             :: Name -> OccName 
109 nameModule              :: Name -> Module
110 nameSrcLoc              :: Name -> SrcLoc
111
112 nameUnique  name = n_uniq name
113 nameOccName name = n_occ  name
114 nameSrcLoc  name = n_loc  name
115
116 nameModule (Name { n_sort = Global mod }) = mod
117 nameModule name                           = pprPanic "nameModule" (ppr name)
118
119 nameModule_maybe (Name { n_sort = Global mod }) = Just mod
120 nameModule_maybe name                           = Nothing
121 \end{code}
122
123 \begin{code}
124 isLocallyDefinedName    :: Name -> Bool
125 isUserExportedName      :: Name -> Bool
126 isLocalName             :: Name -> Bool         -- Not globals
127 isGlobalName            :: Name -> Bool
128 isSystemName            :: Name -> Bool
129 isExternallyVisibleName :: Name -> Bool
130
131 isGlobalName (Name {n_sort = Global _}) = True
132 isGlobalName other                      = False
133
134 isLocalName name = not (isGlobalName name)
135
136 isLocallyDefinedName name = isLocalName name
137
138 -- Global names are by definition those that are visible
139 -- outside the module, *as seen by the linker*.  Externally visible
140 -- does not mean visible at the source level (that's isExported).
141 isExternallyVisibleName name = isGlobalName name
142
143 isUserExportedName (Name { n_sort = Exported }) = True
144 isUserExportedName other                        = False
145
146 isSystemName (Name {n_sort = System}) = True
147 isSystemName other                    = False
148 \end{code}
149
150
151 %************************************************************************
152 %*                                                                      *
153 \subsection{Making names}
154 %*                                                                      *
155 %************************************************************************
156
157 \begin{code}
158 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
159 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
160         -- NB: You might worry that after lots of huffing and
161         -- puffing we might end up with two local names with distinct
162         -- uniques, but the same OccName.  Indeed we can, but that's ok
163         --      * the insides of the compiler don't care: they use the Unique
164         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
165         --        uniques if you get confused
166         --      * for interface files we tidyCore first, which puts the uniques
167         --        into the print name (see setNameVisibility below)
168
169 mkImportedLocalName :: Unique -> OccName -> SrcLoc -> Name
170         -- Just the same as mkLocalName, except the provenance is different
171         -- Reason: this flags the name as one that came in from an interface 
172         -- file. This is useful when trying to decide which of two type
173         -- variables should 'win' when unifying them.
174         -- NB: this is only for non-top-level names, so we use ImplicitImport
175         --
176         -- Oct 00: now that Names lack Provenances, mkImportedLocalName doesn't make
177         --         sense any more, so it's just the same as mkLocalName
178 mkImportedLocalName uniq occ loc = mkLocalName uniq occ loc
179
180
181 mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
182 mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
183                                        n_occ = occ, n_loc = loc }
184                                 
185
186 mkKnownKeyGlobal :: RdrName -> Unique -> Name
187 mkKnownKeyGlobal rdr_name uniq
188   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
189                       (rdrNameOcc rdr_name)
190                       builtinSrcLoc
191
192 mkWiredInName :: Module -> OccName -> Unique -> Name
193 mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
194
195 mkSysLocalName :: Unique -> UserFS -> Name
196 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
197                                 n_occ = mkVarOcc fs, n_loc = noSrcLoc }
198
199 mkCCallName :: Unique -> EncodedString -> Name
200         -- The encoded string completely describes the ccall
201 mkCCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
202                                n_occ = mkCCallOcc str, n_loc = noSrcLoc }
203
204 mkTopName :: Unique -> Module -> FAST_STRING -> Name
205         -- Make a top-level name; make it Global if top-level
206         -- things should be externally visible; Local otherwise
207         -- This chap is only used *after* the tidyCore phase
208         -- Notably, it is used during STG lambda lifting
209         --
210         -- We have to make sure that the name is globally unique
211         -- and we don't have tidyCore to help us. So we append
212         -- the unique.  Hack!  Hack!
213         -- (Used only by the STG lambda lifter.)
214 mkTopName uniq mod fs
215   = Name { n_uniq = uniq, 
216            n_sort = mk_top_sort mod,
217            n_occ  = mkVarOcc (_PK_ ((_UNPK_ fs) ++ show uniq)),
218            n_loc = noSrcLoc }
219
220 mkIPName :: Unique -> OccName -> Name
221 mkIPName uniq occ
222   = Name { n_uniq = uniq,
223            n_sort = Local,
224            n_occ  = occ,
225            n_loc = noSrcLoc }
226
227 ---------------------------------------------------------------------
228 mkDerivedName :: (OccName -> OccName)
229               -> Name           -- Base name
230               -> Unique         -- New unique
231               -> Name           -- Result is always a value name
232
233 mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)}
234 \end{code}
235
236 \begin{code}
237 -- When we renumber/rename things, we need to be
238 -- able to change a Name's Unique to match the cached
239 -- one in the thing it's the name of.  If you know what I mean.
240 setNameUnique name uniq = name {n_uniq = uniq}
241
242 setNameOcc :: Name -> OccName -> Name
243         -- Give the thing a new OccName, *and*
244         -- record that it's no longer a sys-local
245         -- This is used by the tidy-up pass
246 setNameOcc name occ = name {n_occ = occ}
247
248 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
249 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
250                        where
251                          set (Global _) = Global mod
252
253 setLocalNameSort :: Name -> Bool -> Name
254   -- Set the name's sort to Local or Exported, depending on the boolean
255 setLocalNameSort name is_exported = name { n_sort = if is_exported then Exported
256                                                                    else Local }
257 \end{code}
258
259
260 %************************************************************************
261 %*                                                                      *
262 \subsection{Tidying a name}
263 %*                                                                      *
264 %************************************************************************
265
266 tidyTopName is applied to top-level names in the final program
267
268 For top-level things, 
269         it globalises Local names 
270                 (if all top-level things should be visible)
271         and localises non-exported Global names
272                  (if only exported things should be visible)
273
274 In all cases except an exported global, it gives it a new occurrence name.
275
276 The "visibility" here concerns whether the .o file's symbol table
277 mentions the thing; if so, it needs a module name in its symbol.
278 The Global things are "visible" and the Local ones are not
279
280 Why should things be "visible"?  Certainly they must be if they
281 are exported.  But also:
282
283 (a) In certain (prelude only) modules we split up the .hc file into
284     lots of separate little files, which are separately compiled by the C
285     compiler.  That gives lots of little .o files.  The idea is that if
286     you happen to mention one of them you don't necessarily pull them all
287     in.  (Pulling in a piece you don't need can be v bad, because it may
288     mention other pieces you don't need either, and so on.)
289     
290     Sadly, splitting up .hc files means that local names (like s234) are
291     now globally visible, which can lead to clashes between two .hc
292     files. So unlocaliseWhatnot goes through making all the local things
293     into global things, essentially by giving them full names so when they
294     are printed they'll have their module name too.  Pretty revolting
295     really.
296
297 (b) When optimisation is on we want to make all the internal
298     top-level defns externally visible
299
300 \begin{code}
301 tidyTopName :: Module -> TidyOccEnv -> Name -> (TidyOccEnv, Name)
302 tidyTopName mod env
303             name@(Name { n_occ = occ, n_sort = sort, n_uniq = uniq, n_loc = loc })
304   = case sort of
305         System   -> localise            -- System local Ids
306         Local    -> localise            -- User non-exported Ids
307         Exported -> globalise           -- User-exported things
308         Global _ -> no_op               -- Constructors, class selectors etc
309
310   where
311     no_op     = (env, name)
312
313     globalise = (env, name { n_sort = Global mod })     -- Don't change occurrence name
314
315     localise     = (env', name')
316     (env', occ') = tidyOccName env occ
317     name' | all_toplev_ids_visible  = name { n_occ = occ', n_sort = Global mod }
318           | otherwise               = name { n_occ = occ' }
319
320 all_toplev_ids_visible = 
321         not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
322         opt_EnsureSplittableC            -- Splitting requires visiblilty
323 \end{code}
324
325
326
327 %************************************************************************
328 %*                                                                      *
329 \subsection{Predicates and selectors}
330 %*                                                                      *
331 %************************************************************************
332
333 \begin{code}
334 hashName :: Name -> Int
335 hashName name = iBox (u2i (nameUnique name))
336
337
338 nameRdrName :: Name -> RdrName
339 -- Makes a qualified name for top-level (Global) names, whether locally defined or not
340 -- and an unqualified name just for Locals
341 nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrQual (moduleName mod) occ
342 nameRdrName (Name { n_occ = occ })                      = mkRdrUnqual occ
343
344 ifaceNameRdrName :: Name -> RdrName
345 -- Makes a qualified naem for imported things, 
346 -- and an unqualified one for local things
347 ifaceNameRdrName n | isLocallyDefined n = mkRdrUnqual (nameOccName n)
348                    | otherwise          = mkRdrQual   (moduleName (nameModule n)) (nameOccName n) 
349
350 isDllName :: Name -> Bool
351         -- Does this name refer to something in a different DLL?
352 isDllName nm = not opt_Static &&
353                not (isLocallyDefinedName nm) &&         -- isLocallyDefinedName test needed 'cos
354                not (isModuleInThisPackage (nameModule nm))      -- nameModule won't work on local names
355
356
357
358 isTyVarName :: Name -> Bool
359 isTyVarName name = isTvOcc (nameOccName name)
360
361 \end{code}
362
363
364 %************************************************************************
365 %*                                                                      *
366 \subsection[Name-instances]{Instance declarations}
367 %*                                                                      *
368 %************************************************************************
369
370 \begin{code}
371 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
372 \end{code}
373
374 \begin{code}
375 instance Eq Name where
376     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
377     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
378
379 instance Ord Name where
380     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
381     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
382     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
383     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
384     compare a b = cmpName a b
385
386 instance Uniquable Name where
387     getUnique = nameUnique
388
389 instance NamedThing Name where
390     getName n = n
391 \end{code}
392
393
394 %************************************************************************
395 %*                                                                      *
396 \subsection{Name environment}
397 %*                                                                      *
398 %************************************************************************
399
400 \begin{code}
401 type NameEnv a = UniqFM a       -- Domain is Name
402
403 emptyNameEnv     :: NameEnv a
404 mkNameEnv        :: [(Name,a)] -> NameEnv a
405 nameEnvElts      :: NameEnv a -> [a]
406 extendNameEnv_C  :: (a->a->a) -> NameEnv a -> Name -> a -> NameEnv a
407 extendNameEnv    :: NameEnv a -> Name -> a -> NameEnv a
408 plusNameEnv      :: NameEnv a -> NameEnv a -> NameEnv a
409 plusNameEnv_C    :: (a->a->a) -> NameEnv a -> NameEnv a -> NameEnv a
410 extendNameEnvList:: NameEnv a -> [(Name,a)] -> NameEnv a
411 delFromNameEnv   :: NameEnv a -> Name -> NameEnv a
412 elemNameEnv      :: Name -> NameEnv a -> Bool
413 unitNameEnv      :: Name -> a -> NameEnv a
414 lookupNameEnv    :: NameEnv a -> Name -> Maybe a
415 lookupNameEnv_NF :: NameEnv a -> Name -> a
416 mapNameEnv       :: (a->b) -> NameEnv a -> NameEnv b
417
418 emptyNameEnv     = emptyUFM
419 mkNameEnv        = listToUFM
420 nameEnvElts      = eltsUFM
421 extendNameEnv_C  = addToUFM_C
422 extendNameEnv    = addToUFM
423 plusNameEnv      = plusUFM
424 plusNameEnv_C    = plusUFM_C
425 extendNameEnvList= addListToUFM
426 delFromNameEnv   = delFromUFM
427 elemNameEnv      = elemUFM
428 mapNameEnv       = mapUFM
429 unitNameEnv      = unitUFM
430
431 lookupNameEnv          = lookupUFM
432 lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupUFM env n)
433 \end{code}
434
435
436 %************************************************************************
437 %*                                                                      *
438 \subsection{Pretty printing}
439 %*                                                                      *
440 %************************************************************************
441
442 \begin{code}
443 instance Outputable Name where
444         -- When printing interfaces, all Locals have been given nice print-names
445     ppr name = pprName name
446
447 pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
448   = getPprStyle $ \ sty ->
449     case sort of
450       Global mod -> pprGlobal sty uniq mod occ
451       System     -> pprSysLocal sty uniq occ
452       Local      -> pprLocal sty uniq occ empty
453       Exported   -> pprLocal sty uniq occ (char 'x')
454
455 pprLocal sty uniq occ pp_export
456   | codeStyle sty  = pprUnique uniq
457   | debugStyle sty = pprOccName occ <> 
458                      text "{-" <> pp_export <+> pprUnique10 uniq <> text "-}"
459   | otherwise      = pprOccName occ
460
461 pprGlobal sty uniq mod occ
462   | codeStyle sty         = ppr (moduleName mod) <> char '_' <> pprOccName occ
463   | debugStyle sty        = ppr (moduleName mod) <> dot <> pprOccName occ <> 
464                             text "{-" <> pprUnique10 uniq <> text "-}"
465   | printModulePrefix mod = ppr (moduleName mod) <> dot <> pprOccName occ
466   | otherwise             = pprOccName occ
467
468 pprSysLocal sty uniq occ
469   | codeStyle sty  = pprUnique uniq
470   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
471 \end{code}
472
473
474 %************************************************************************
475 %*                                                                      *
476 \subsection{Overloaded functions related to Names}
477 %*                                                                      *
478 %************************************************************************
479
480 \begin{code}
481 class NamedThing a where
482     getOccName :: a -> OccName
483     getName    :: a -> Name
484
485     getOccName n = nameOccName (getName n)      -- Default method
486 \end{code}
487
488 \begin{code}
489 getSrcLoc           :: NamedThing a => a -> SrcLoc
490 isLocallyDefined    :: NamedThing a => a -> Bool
491 getOccString        :: NamedThing a => a -> String
492 toRdrName           :: NamedThing a => a -> RdrName
493
494 getSrcLoc           = nameSrcLoc           . getName
495 isLocallyDefined    = isLocallyDefinedName . getName
496 getOccString        = occNameString        . getOccName
497 toRdrName           = ifaceNameRdrName     . getName
498 \end{code}
499
500 \begin{code}
501 {-# SPECIALIZE isLocallyDefined :: Name -> Bool #-}
502 \end{code}