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