[project @ 2000-11-24 17:02:01 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, mkSysLocalName, mkCCallName,
14         mkIPName,
15         mkDerivedName, mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
16
17         nameUnique, setNameUnique,
18         nameOccName, nameModule, nameModule_maybe,
19         setNameOcc, nameRdrName, setNameModuleAndLoc, 
20         toRdrName, hashName, 
21         globaliseName, localiseName,
22
23         nameSrcLoc, nameIsLocallyDefined, isDllName, nameIsFrom, nameIsLocalOrFrom,
24
25         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
26         isTyVarName,
27         
28         -- Environment
29         NameEnv, mkNameEnv,
30         emptyNameEnv, unitNameEnv, nameEnvElts, 
31         extendNameEnv_C, extendNameEnv, foldNameEnv, filterNameEnv,
32         plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList,
33         lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, 
34
35
36         -- Class NamedThing and overloaded friends
37         NamedThing(..),
38         getSrcLoc, getOccString, toRdrName,
39         isFrom, isLocalOrFrom
40     ) where
41
42 #include "HsVersions.h"
43
44 import OccName          -- All of it
45 import Module           ( Module, moduleName, mkVanillaModule, isHomeModule )
46 import RdrName          ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule )
47 import CmdLineOpts      ( opt_Static )
48 import SrcLoc           ( builtinSrcLoc, noSrcLoc, SrcLoc )
49 import Unique           ( Unique, Uniquable(..), u2i, pprUnique, pprUnique10 )
50 import FastTypes
51 import Maybes           ( expectJust )
52 import UniqFM
53 import Outputable
54 \end{code}
55
56 %************************************************************************
57 %*                                                                      *
58 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
59 %*                                                                      *
60 %************************************************************************
61  
62 \begin{code}
63 data Name = Name {
64                 n_sort :: NameSort,     -- What sort of name it is
65                 n_occ  :: OccName,      -- Its occurrence name
66                 n_uniq :: Unique,
67                 n_loc  :: SrcLoc        -- Definition site
68             }
69
70 data NameSort
71   = Global Module       -- (a) TyCon, Class, their derived Ids, dfun Id
72                         -- (b) Imported Id
73                         -- (c) Top-level Id in the original source, even if
74                         --      locally defined
75
76   | Local               -- A user-defined Id or TyVar
77                         -- defined in the module being compiled
78
79   | System              -- A system-defined Id or TyVar.  Typically the
80                         -- OccName is very uninformative (like 's')
81 \end{code}
82
83 Notes about the NameSorts:
84
85 1.  Initially, top-level Ids (including locally-defined ones) get Global names, 
86     and all other local Ids get Local names
87
88 2.  Things with a @Global@ name are given C static labels, so they finally
89     appear in the .o file's symbol table.  They appear in the symbol table
90     in the form M.n.  If originally-local things have this property they
91     must be made @Global@ first.
92
93 3.  In the tidy-core phase, a Global that is not visible to an importer
94     is changed to Local, and a Local that is visible is changed to Global
95
96 4.  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 nameIsLocallyDefined    :: Name -> Bool
125 nameIsFrom              :: Module -> Name -> Bool
126 nameIsLocalOrFrom       :: Module -> Name -> Bool
127 isLocalName             :: Name -> Bool         -- Not globals
128 isGlobalName            :: Name -> Bool
129 isSystemName            :: Name -> Bool
130 isExternallyVisibleName :: Name -> Bool
131
132 isGlobalName (Name {n_sort = Global _}) = True
133 isGlobalName other                      = False
134
135 isLocalName name = not (isGlobalName name)
136
137 nameIsLocallyDefined name = isLocalName name
138
139 nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from
140 nameIsLocalOrFrom from other                        = True
141
142 nameIsFrom from (Name {n_sort = Global mod}) = mod == from
143 nameIsFrom from other                        = pprPanic "nameIsFrom" (ppr other)
144
145 -- Global names are by definition those that are visible
146 -- outside the module, *as seen by the linker*.  Externally visible
147 -- does not mean visible at the source level
148 isExternallyVisibleName name = isGlobalName name
149
150 isSystemName (Name {n_sort = System}) = True
151 isSystemName other                    = False
152 \end{code}
153
154
155 %************************************************************************
156 %*                                                                      *
157 \subsection{Making names}
158 %*                                                                      *
159 %************************************************************************
160
161 \begin{code}
162 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
163 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
164         -- NB: You might worry that after lots of huffing and
165         -- puffing we might end up with two local names with distinct
166         -- uniques, but the same OccName.  Indeed we can, but that's ok
167         --      * the insides of the compiler don't care: they use the Unique
168         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
169         --        uniques if you get confused
170         --      * for interface files we tidyCore first, which puts the uniques
171         --        into the print name (see setNameVisibility below)
172
173 mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
174 mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
175                                        n_occ = occ, n_loc = loc }
176
177 mkKnownKeyGlobal :: RdrName -> Unique -> Name
178 mkKnownKeyGlobal rdr_name uniq
179   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
180                       (rdrNameOcc rdr_name)
181                       builtinSrcLoc
182
183 mkWiredInName :: Module -> OccName -> Unique -> Name
184 mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
185
186 mkSysLocalName :: Unique -> UserFS -> Name
187 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
188                                 n_occ = mkVarOcc fs, n_loc = noSrcLoc }
189
190 mkCCallName :: Unique -> EncodedString -> Name
191         -- The encoded string completely describes the ccall
192 mkCCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
193                                n_occ = mkCCallOcc str, n_loc = noSrcLoc }
194
195 mkIPName :: Unique -> OccName -> Name
196 mkIPName uniq occ
197   = Name { n_uniq = uniq,
198            n_sort = Local,
199            n_occ  = occ,
200            n_loc = noSrcLoc }
201
202 ---------------------------------------------------------------------
203 mkDerivedName :: (OccName -> OccName)
204               -> Name           -- Base name
205               -> Unique         -- New unique
206               -> Name           -- Result is always a value name
207
208 mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)}
209 \end{code}
210
211 \begin{code}
212 -- When we renumber/rename things, we need to be
213 -- able to change a Name's Unique to match the cached
214 -- one in the thing it's the name of.  If you know what I mean.
215 setNameUnique name uniq = name {n_uniq = uniq}
216
217 setNameOcc :: Name -> OccName -> Name
218 setNameOcc name occ = name {n_occ = occ}
219
220 globaliseName :: Name -> Module -> Name
221 globaliseName n mod = n { n_sort = Global mod }
222                                 
223 localiseName :: Name -> Name
224 localiseName n = n { n_sort = Local }
225                                 
226 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
227 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
228                        where
229                          set (Global _) = Global mod
230 \end{code}
231
232
233 %************************************************************************
234 %*                                                                      *
235 \subsection{Predicates and selectors}
236 %*                                                                      *
237 %************************************************************************
238
239 \begin{code}
240 hashName :: Name -> Int
241 hashName name = iBox (u2i (nameUnique name))
242
243
244 nameRdrName :: Name -> RdrName
245 -- Makes a qualified name for top-level (Global) names, whether locally defined or not
246 -- and an unqualified name just for Locals
247 nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ
248 nameRdrName (Name { n_occ = occ })                      = mkRdrUnqual occ
249
250 isDllName :: Name -> Bool
251         -- Does this name refer to something in a different DLL?
252 isDllName nm = not opt_Static &&
253                not (isLocalName nm) &&                          -- isLocalName test needed 'cos
254                not (isHomeModule (nameModule nm))       -- nameModule won't work on local names
255
256
257
258 isTyVarName :: Name -> Bool
259 isTyVarName name = isTvOcc (nameOccName name)
260 \end{code}
261
262
263 %************************************************************************
264 %*                                                                      *
265 \subsection[Name-instances]{Instance declarations}
266 %*                                                                      *
267 %************************************************************************
268
269 \begin{code}
270 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
271 \end{code}
272
273 \begin{code}
274 instance Eq Name where
275     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
276     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
277
278 instance Ord Name where
279     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
280     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
281     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
282     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
283     compare a b = cmpName a b
284
285 instance Uniquable Name where
286     getUnique = nameUnique
287
288 instance NamedThing Name where
289     getName n = n
290 \end{code}
291
292
293 %************************************************************************
294 %*                                                                      *
295 \subsection{Name environment}
296 %*                                                                      *
297 %************************************************************************
298
299 \begin{code}
300 type NameEnv a = UniqFM a       -- Domain is Name
301
302 emptyNameEnv     :: NameEnv a
303 mkNameEnv        :: [(Name,a)] -> NameEnv a
304 nameEnvElts      :: NameEnv a -> [a]
305 extendNameEnv_C  :: (a->a->a) -> NameEnv a -> Name -> a -> NameEnv a
306 extendNameEnv    :: NameEnv a -> Name -> a -> NameEnv a
307 plusNameEnv      :: NameEnv a -> NameEnv a -> NameEnv a
308 plusNameEnv_C    :: (a->a->a) -> NameEnv a -> NameEnv a -> NameEnv a
309 extendNameEnvList:: NameEnv a -> [(Name,a)] -> NameEnv a
310 delFromNameEnv   :: NameEnv a -> Name -> NameEnv a
311 elemNameEnv      :: Name -> NameEnv a -> Bool
312 unitNameEnv      :: Name -> a -> NameEnv a
313 lookupNameEnv    :: NameEnv a -> Name -> Maybe a
314 lookupNameEnv_NF :: NameEnv a -> Name -> a
315 mapNameEnv       :: (a->b) -> NameEnv a -> NameEnv b
316 foldNameEnv      :: (a -> b -> b) -> b -> NameEnv a -> b
317 filterNameEnv    :: (elt -> Bool) -> NameEnv elt -> NameEnv elt
318
319 emptyNameEnv     = emptyUFM
320 foldNameEnv      = foldUFM
321 mkNameEnv        = listToUFM
322 nameEnvElts      = eltsUFM
323 extendNameEnv_C  = addToUFM_C
324 extendNameEnv    = addToUFM
325 plusNameEnv      = plusUFM
326 plusNameEnv_C    = plusUFM_C
327 extendNameEnvList= addListToUFM
328 delFromNameEnv   = delFromUFM
329 elemNameEnv      = elemUFM
330 mapNameEnv       = mapUFM
331 unitNameEnv      = unitUFM
332 filterNameEnv    = filterUFM
333
334 lookupNameEnv          = lookupUFM
335 lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupUFM env n)
336 \end{code}
337
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection{Pretty printing}
342 %*                                                                      *
343 %************************************************************************
344
345 \begin{code}
346 instance Outputable Name where
347         -- When printing interfaces, all Locals have been given nice print-names
348     ppr name = pprName name
349
350 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
351   = getPprStyle $ \ sty ->
352     case sort of
353       Global mod -> pprGlobal sty name uniq mod occ
354       System     -> pprSysLocal sty uniq occ
355       Local      -> pprLocal sty uniq occ
356
357 pprLocal sty uniq occ
358   | codeStyle sty  = pprUnique uniq
359   | debugStyle sty = pprOccName occ <> 
360                      text "{-" <> pprUnique10 uniq <> text "-}"
361   | otherwise      = pprOccName occ
362
363 pprGlobal sty name uniq mod occ
364   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
365
366   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
367                             text "{-" <> pprUnique10 uniq <> text "-}"
368
369   | unqualStyle sty name = pprOccName occ
370   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
371
372 pprSysLocal sty uniq occ
373   | codeStyle sty  = pprUnique uniq
374   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
375 \end{code}
376
377
378 %************************************************************************
379 %*                                                                      *
380 \subsection{Overloaded functions related to Names}
381 %*                                                                      *
382 %************************************************************************
383
384 \begin{code}
385 class NamedThing a where
386     getOccName :: a -> OccName
387     getName    :: a -> Name
388
389     getOccName n = nameOccName (getName n)      -- Default method
390 \end{code}
391
392 \begin{code}
393 getSrcLoc           :: NamedThing a => a -> SrcLoc
394 getOccString        :: NamedThing a => a -> String
395 toRdrName           :: NamedThing a => a -> RdrName
396 isFrom              :: NamedThing a => Module -> a -> Bool
397 isLocalOrFrom       :: NamedThing a => Module -> a -> Bool
398
399 getSrcLoc           = nameSrcLoc           . getName
400 getOccString        = occNameString        . getOccName
401 toRdrName           = nameRdrName          . getName
402 isFrom mod x        = nameIsFrom mod (getName x)
403 isLocalOrFrom mod x = nameIsLocalOrFrom mod ( getName x)
404 \end{code}
405