b7b9ed238c12a8456cb827dbb1cebf7bf8446b0e
[ghc-hetmet.git] / ghc / compiler / basicTypes / RdrName.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4
5 \section[RdrName]{@RdrName@}
6
7 \begin{code}
8 module RdrName (
9         RdrName(..),    -- Constructors exported only to BinIface
10
11         -- Construction
12         mkRdrUnqual, mkRdrQual, 
13         mkUnqual, mkVarUnqual, mkQual, mkOrig,
14         nameRdrName, getRdrName, 
15         mkDerivedRdrName, 
16
17         -- Destruction
18         rdrNameModule, rdrNameOcc, setRdrNameSpace,
19         isRdrDataCon, isRdrTyVar, isRdrTc, isQual, isUnqual, 
20         isOrig, isOrig_maybe, isExact, isExact_maybe, isSrcRdrName,
21
22         -- Printing;    instance Outputable RdrName
23
24         -- LocalRdrEnv
25         LocalRdrEnv, emptyLocalRdrEnv, extendLocalRdrEnv,
26         lookupLocalRdrEnv, elemLocalRdrEnv,
27
28         -- GlobalRdrEnv
29         GlobalRdrEnv, emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv, 
30         lookupGlobalRdrEnv, pprGlobalRdrEnv, globalRdrEnvElts,
31         lookupGRE_RdrName, lookupGRE_Name,
32
33         -- GlobalRdrElt, Provenance, ImportSpec
34         GlobalRdrElt(..), Provenance(..), ImportSpec(..),
35         isLocalGRE, unQualOK,
36         pprNameProvenance
37   ) where 
38
39 #include "HsVersions.h"
40
41 import OccName  ( NameSpace, tcName, varName,
42                   OccName, UserFS, EncodedFS,
43                   mkSysOccFS, setOccNameSpace,
44                   mkOccFS, mkVarOcc, occNameFlavour,
45                   isDataOcc, isTvOcc, isTcOcc,
46                   OccEnv, emptyOccEnv, extendOccEnvList, lookupOccEnv, 
47                   elemOccEnv, plusOccEnv_C, extendOccEnv_C, foldOccEnv,
48                   occEnvElts
49                 )
50 import Module   ( ModuleName, mkSysModuleNameFS, mkModuleNameFS )
51 import Name     ( Name, NamedThing(getName), nameModuleName, nameParent_maybe,
52                   nameOccName, isExternalName, nameSrcLoc )
53 import Maybes   ( seqMaybe )
54 import SrcLoc   ( SrcLoc, isGoodSrcLoc, SrcSpan )
55 import BasicTypes( DeprecTxt )
56 import Outputable
57 import Util     ( thenCmp )
58 \end{code}
59
60
61 %************************************************************************
62 %*                                                                      *
63 \subsection{The main data type}
64 %*                                                                      *
65 %************************************************************************
66
67 \begin{code}
68 data RdrName 
69   = Unqual OccName
70         -- Used for ordinary, unqualified occurrences 
71
72   | Qual ModuleName OccName
73         -- A qualified name written by the user in 
74         -- *source* code.  The module isn't necessarily 
75         -- the module where the thing is defined; 
76         -- just the one from which it is imported
77
78   | Orig ModuleName OccName
79         -- An original name; the module is the *defining* module.
80         -- This is used when GHC generates code that will be fed
81         -- into the renamer (e.g. from deriving clauses), but where
82         -- we want to say "Use Prelude.map dammit".  
83  
84   | Exact Name
85         -- We know exactly the Name. This is used 
86         --  (a) when the parser parses built-in syntax like "[]" 
87         --      and "(,)", but wants a RdrName from it
88         --  (b) when converting names to the RdrNames in IfaceTypes
89         --      Here an Exact RdrName always contains an External Name
90         --      (Internal Names are converted to simple Unquals)
91         --  (c) possibly, by the meta-programming stuff
92 \end{code}
93
94
95 %************************************************************************
96 %*                                                                      *
97 \subsection{Simple functions}
98 %*                                                                      *
99 %************************************************************************
100
101 \begin{code}
102 rdrNameModule :: RdrName -> ModuleName
103 rdrNameModule (Qual m _) = m
104 rdrNameModule (Orig m _) = m
105 rdrNameModule (Exact n)  = nameModuleName n
106 rdrNameModule (Unqual n) = pprPanic "rdrNameModule" (ppr n)
107
108 rdrNameOcc :: RdrName -> OccName
109 rdrNameOcc (Qual _ occ) = occ
110 rdrNameOcc (Unqual occ) = occ
111 rdrNameOcc (Orig _ occ) = occ
112 rdrNameOcc (Exact name) = nameOccName name
113
114 setRdrNameSpace :: RdrName -> NameSpace -> RdrName
115 -- This rather gruesome function is used mainly by the parser
116 -- When parsing         data T a = T | T1 Int
117 -- we parse the data constructors as *types* because of parser ambiguities,
118 -- so then we need to change the *type constr* to a *data constr*
119 --
120 -- The original-name case *can* occur when parsing
121 --              data [] a = [] | a : [a]
122 -- For the orig-name case we return an unqualified name.
123 setRdrNameSpace (Unqual occ) ns = Unqual (setOccNameSpace ns occ)
124 setRdrNameSpace (Qual m occ) ns = Qual m (setOccNameSpace ns occ)
125 setRdrNameSpace (Orig m occ) ns = Orig m (setOccNameSpace ns occ)
126 setRdrNameSpace (Exact n)    ns = Orig (nameModuleName n)
127                                        (setOccNameSpace ns (nameOccName n))
128 \end{code}
129
130 \begin{code}
131         -- These two are the basic constructors
132 mkRdrUnqual :: OccName -> RdrName
133 mkRdrUnqual occ = Unqual occ
134
135 mkRdrQual :: ModuleName -> OccName -> RdrName
136 mkRdrQual mod occ = Qual mod occ
137
138 mkOrig :: ModuleName -> OccName -> RdrName
139 mkOrig mod occ = Orig mod occ
140
141 ---------------
142 mkDerivedRdrName :: Name -> (OccName -> OccName) -> (RdrName)
143 mkDerivedRdrName parent mk_occ
144   = mkOrig (nameModuleName parent) (mk_occ (nameOccName parent))
145
146 ---------------
147         -- These two are used when parsing source files
148         -- They do encode the module and occurrence names
149 mkUnqual :: NameSpace -> UserFS -> RdrName
150 mkUnqual sp n = Unqual (mkOccFS sp n)
151
152 mkVarUnqual :: UserFS -> RdrName
153 mkVarUnqual n = Unqual (mkOccFS varName n)
154
155 mkQual :: NameSpace -> (UserFS, UserFS) -> RdrName
156 mkQual sp (m, n) = Qual (mkModuleNameFS m) (mkOccFS sp n)
157
158 getRdrName :: NamedThing thing => thing -> RdrName
159 getRdrName name = nameRdrName (getName name)
160
161 nameRdrName :: Name -> RdrName
162 nameRdrName name = Exact name
163 -- Keep the Name even for Internal names, so that the
164 -- unique is still there for debug printing, particularly
165 -- of Types (which are converted to IfaceTypes before printing)
166
167 nukeExact :: Name -> RdrName
168 nukeExact n 
169   | isExternalName n = Orig (nameModuleName n) (nameOccName n)
170   | otherwise        = Unqual (nameOccName n)
171 \end{code}
172
173 \begin{code}
174 isRdrDataCon rn = isDataOcc (rdrNameOcc rn)
175 isRdrTyVar   rn = isTvOcc   (rdrNameOcc rn)
176 isRdrTc      rn = isTcOcc   (rdrNameOcc rn)
177
178 isSrcRdrName (Unqual _) = True
179 isSrcRdrName (Qual _ _) = True
180 isSrcRdrName _          = False
181
182 isUnqual (Unqual _) = True
183 isUnqual other      = False
184
185 isQual (Qual _ _) = True
186 isQual _          = False
187
188 isOrig (Orig _ _) = True
189 isOrig _          = False
190
191 isOrig_maybe (Orig m n) = Just (m,n)
192 isOrig_maybe _          = Nothing
193
194 isExact (Exact _) = True
195 isExact other   = False
196
197 isExact_maybe (Exact n) = Just n
198 isExact_maybe other     = Nothing
199 \end{code}
200
201
202 %************************************************************************
203 %*                                                                      *
204 \subsection{Instances}
205 %*                                                                      *
206 %************************************************************************
207
208 \begin{code}
209 instance Outputable RdrName where
210     ppr (Exact name)   = ppr name
211     ppr (Unqual occ)   = ppr occ <+> ppr_name_space occ
212     ppr (Qual mod occ) = ppr mod <> dot <> ppr occ <+> ppr_name_space occ
213     ppr (Orig mod occ) = ppr mod <> dot <> ppr occ <+> ppr_name_space occ
214
215 ppr_name_space occ = ifPprDebug (parens (text (occNameFlavour occ)))
216
217 instance OutputableBndr RdrName where
218     pprBndr _ n 
219         | isTvOcc (rdrNameOcc n) = char '@' <+> ppr n
220         | otherwise              = ppr n
221
222 instance Eq RdrName where
223     (Exact n1)    == (Exact n2)    = n1==n2
224         -- Convert exact to orig
225     (Exact n1)    == r2@(Orig _ _) = nukeExact n1 == r2
226     r1@(Orig _ _) == (Exact n2)    = r1 == nukeExact n2
227
228     (Orig m1 o1)  == (Orig m2 o2)  = m1==m2 && o1==o2
229     (Qual m1 o1)  == (Qual m2 o2)  = m1==m2 && o1==o2
230     (Unqual o1)   == (Unqual o2)   = o1==o2
231     r1 == r2 = False
232
233 instance Ord RdrName where
234     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
235     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
236     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
237     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
238
239         -- Unqual < Qual < Orig
240         -- We always convert Exact to Orig before comparing
241     compare (Exact n1) (Exact n2) | n1==n2 = EQ -- Short cut
242                                   | otherwise = nukeExact n1 `compare` nukeExact n2
243     compare (Exact n1) n2                     = nukeExact n1 `compare` n2
244     compare n1        (Exact n2)              = n1 `compare` nukeExact n2
245
246
247     compare (Qual m1 o1) (Qual m2 o2) = (o1 `compare` o2) `thenCmp` (m1 `compare` m2) 
248     compare (Orig m1 o1) (Orig m2 o2) = (o1 `compare` o2) `thenCmp` (m1 `compare` m2) 
249     compare (Unqual o1)  (Unqual  o2) = o1 `compare` o2
250  
251     compare (Unqual _)   _            = LT
252     compare (Qual _ _)   (Orig _ _)   = LT
253     compare _            _            = GT
254 \end{code}
255
256
257
258 %************************************************************************
259 %*                                                                      *
260                         LocalRdrEnv
261 %*                                                                      *
262 %************************************************************************
263
264 A LocalRdrEnv is used for local bindings (let, where, lambda, case)
265 It is keyed by OccName, because we never use it for qualified names.
266
267 \begin{code}
268 type LocalRdrEnv = OccEnv Name
269
270 emptyLocalRdrEnv = emptyOccEnv
271
272 extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv
273 extendLocalRdrEnv env names
274   = extendOccEnvList env [(nameOccName n, n) | n <- names]
275
276 lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
277 lookupLocalRdrEnv env (Exact name) = Just name
278 lookupLocalRdrEnv env (Unqual occ) = lookupOccEnv env occ
279 lookupLocalRdrEnv env other        = Nothing
280
281 elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
282 elemLocalRdrEnv rdr_name env 
283   | isUnqual rdr_name = rdrNameOcc rdr_name `elemOccEnv` env
284   | otherwise         = False
285 \end{code}
286
287
288 %************************************************************************
289 %*                                                                      *
290                         GlobalRdrEnv
291 %*                                                                      *
292 %************************************************************************
293
294 \begin{code}
295 type GlobalRdrEnv = OccEnv [GlobalRdrElt]
296         -- Keyed by OccName; when looking up a qualified name
297         -- we look up the OccName part, and then check the Provenance
298         -- to see if the appropriate qualification is valid.  This
299         -- saves routinely doubling the size of the env by adding both
300         -- qualified and unqualified names to the domain.
301         --
302         -- The list in the range is reqd because there may be name clashes
303         -- These only get reported on lookup, not on construction
304
305         -- INVARIANT: All the members of the list have distinct 
306         --            gre_name fields; that is, no duplicate Names
307
308 emptyGlobalRdrEnv = emptyOccEnv
309
310 globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
311 globalRdrEnvElts env = foldOccEnv (++) [] env
312
313 data GlobalRdrElt 
314   = GRE { gre_name   :: Name,
315           gre_prov   :: Provenance,     -- Why it's in scope
316           gre_deprec :: Maybe DeprecTxt -- Whether this name is deprecated
317     }
318
319 instance Outputable GlobalRdrElt where
320   ppr gre = ppr name <+> pp_parent (nameParent_maybe name)
321                 <+> parens (pprNameProvenance gre)
322           where
323             name = gre_name gre
324             pp_parent (Just p) = brackets (text "parent:" <+> ppr p)
325             pp_parent Nothing  = empty
326
327 pprGlobalRdrEnv :: GlobalRdrEnv -> SDoc
328 pprGlobalRdrEnv env
329   = vcat (map pp (occEnvElts env))
330   where
331     pp gres = ppr (nameOccName (gre_name (head gres))) <> colon <+> 
332               vcat [ ppr (gre_name gre) <+> pprNameProvenance gre
333                    | gre <- gres]
334 \end{code}
335
336 \begin{code}
337 lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
338 lookupGlobalRdrEnv env rdr_name = case lookupOccEnv env rdr_name of
339                                         Nothing   -> []
340                                         Just gres -> gres
341
342 lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
343 lookupGRE_RdrName rdr_name env
344   = case lookupOccEnv env occ of
345         Nothing -> []
346         Just gres | isUnqual rdr_name -> filter unQualOK gres
347                   | otherwise         -> filter (hasQual mod) gres
348   where
349     mod = rdrNameModule rdr_name
350     occ = rdrNameOcc rdr_name
351
352 lookupGRE_Name :: GlobalRdrEnv -> Name -> [GlobalRdrElt]
353 lookupGRE_Name env name
354   = [ gre | gre <- lookupGlobalRdrEnv env (nameOccName name),
355             gre_name gre == name ]
356
357
358 isLocalGRE :: GlobalRdrElt -> Bool
359 isLocalGRE (GRE {gre_prov = LocalDef _}) = True
360 isLocalGRE other                         = False
361
362 unQualOK :: GlobalRdrElt -> Bool
363 -- An unqualifed version of this thing is in scope
364 unQualOK (GRE {gre_prov = LocalDef _})    = True
365 unQualOK (GRE {gre_prov = Imported is _}) = not (all is_qual is)
366
367 hasQual :: ModuleName -> GlobalRdrElt -> Bool
368 -- A qualified version of this thing is in scope
369 hasQual mod (GRE {gre_prov = LocalDef m})    = m == mod
370 hasQual mod (GRE {gre_prov = Imported is _}) = any ((== mod) . is_as) is
371
372 plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
373 plusGlobalRdrEnv env1 env2 = plusOccEnv_C (foldr insertGRE) env1 env2
374
375 mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
376 mkGlobalRdrEnv gres
377   = foldr add emptyGlobalRdrEnv gres
378   where
379     add gre env = extendOccEnv_C (foldr insertGRE) env 
380                                  (nameOccName (gre_name gre)) 
381                                  [gre]
382
383 insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
384 insertGRE new_g [] = [new_g]
385 insertGRE new_g (old_g : old_gs)
386         | gre_name new_g == gre_name old_g
387         = new_g `plusGRE` old_g : old_gs
388         | otherwise
389         = old_g : insertGRE new_g old_gs
390
391 plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
392 -- Used when the gre_name fields match
393 plusGRE g1 g2
394   = GRE { gre_name   = gre_name g1,
395           gre_prov   = gre_prov g1 `plusProv` gre_prov g2,
396           gre_deprec = gre_deprec g1 `seqMaybe` gre_deprec g2 }
397         -- Could the deprecs be different?  If we re-export
398         -- something deprecated, is it propagated?  I forget.
399 \end{code}
400
401
402 %************************************************************************
403 %*                                                                      *
404                         Provenance
405 %*                                                                      *
406 %************************************************************************
407
408 The "provenance" of something says how it came to be in scope.
409
410 \begin{code}
411 data Provenance
412   = LocalDef            -- Defined locally
413         ModuleName
414
415   | Imported            -- Imported
416         [ImportSpec]    -- INVARIANT: non-empty
417         Bool            -- True iff the thing was named *explicitly* 
418                         -- in *any* of the import specs rather than being 
419                         -- imported as part of a group; 
420         -- e.g.
421         --      import B
422         --      import C( T(..) )
423         -- Here, everything imported by B, and the constructors of T
424         -- are not named explicitly; only T is named explicitly.
425         -- This info is used when warning of unused names.
426
427 data ImportSpec         -- Describes a particular import declaration
428                         -- Shared among all the Provenaces for a particular
429                         -- import declaration
430   = ImportSpec {
431         is_mod  :: ModuleName,          -- 'import Muggle'
432                                         -- Note the Muggle may well not be 
433                                         -- the defining module for this thing!
434         is_as   :: ModuleName,          -- 'as M' (or 'Muggle' if there is no 'as' clause)
435         is_qual :: Bool,                -- True <=> qualified (only)
436         is_loc  :: SrcSpan }            -- Location of import statment
437
438 -- Comparison of provenance is just used for grouping 
439 -- error messages (in RnEnv.warnUnusedBinds)
440 instance Eq Provenance where
441   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
442
443 instance Eq ImportSpec where
444   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
445
446 instance Ord Provenance where
447    compare (LocalDef _) (LocalDef _)   = EQ
448    compare (LocalDef _) (Imported _ _) = LT
449    compare (Imported _ _) (LocalDef _) = GT
450    compare (Imported is1 _) (Imported is2 _) = compare (head is1) (head is2)
451
452 instance Ord ImportSpec where
453    compare is1 is2 = (is_mod is1 `compare` is_mod is2) `thenCmp` 
454                      (is_loc is1 `compare` is_loc is2)
455 \end{code}
456
457 \begin{code}
458 plusProv :: Provenance -> Provenance -> Provenance
459 -- Choose LocalDef over Imported
460 -- There is an obscure bug lurking here; in the presence
461 -- of recursive modules, something can be imported *and* locally
462 -- defined, and one might refer to it with a qualified name from
463 -- the import -- but I'm going to ignore that because it makes
464 -- the isLocalGRE predicate so much nicer this way
465 plusProv (LocalDef m1) (LocalDef m2) 
466   = pprPanic "plusProv" (ppr m1 <+> ppr m2)
467 plusProv p1@(LocalDef _) p2 = p1
468 plusProv p1 p2@(LocalDef _) = p2
469 plusProv (Imported is1 ex1) (Imported is2 ex2) 
470   = Imported (is1++is2) (ex1 || ex2)
471
472 pprNameProvenance :: GlobalRdrElt -> SDoc
473 pprNameProvenance (GRE {gre_name = name, gre_prov = LocalDef _})
474   = ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
475 pprNameProvenance (GRE {gre_name = name, gre_prov = Imported (why:whys) _})
476   = sep [ppr_reason why, nest 2 (ppr_defn (nameSrcLoc name))]
477
478 ppr_reason imp_spec
479  = ptext SLIT("imported from") <+> ppr (is_mod imp_spec) 
480         <+> ptext SLIT("at") <+> ppr (is_loc imp_spec)
481
482 ppr_defn loc | isGoodSrcLoc loc = parens (ptext SLIT("defined at") <+> ppr loc)
483              | otherwise        = empty
484 \end{code}