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