[project @ 1999-01-27 14:51:14 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnEnv.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[RnEnv]{Environment manipulation for the renamer monad}
5
6 \begin{code}
7 module RnEnv where              -- Export everything
8
9 #include "HsVersions.h"
10
11 import CmdLineOpts      ( opt_WarnNameShadowing, opt_WarnUnusedMatches,
12                           opt_WarnUnusedBinds, opt_WarnUnusedImports )
13 import HsSyn
14 import RdrHsSyn         ( RdrNameIE )
15 import RdrName          ( RdrName, rdrNameModule, rdrNameOcc, isQual, mkRdrUnqual, qualifyRdrName )
16 import HsTypes          ( getTyVarName, replaceTyVarName )
17 import BasicTypes       ( Fixity(..), FixityDirection(..) )
18 import RnMonad
19 import Name             ( Name, Provenance(..), ExportFlag(..), NamedThing(..),
20                           ImportReason(..), getSrcLoc, 
21                           mkLocalName, mkGlobalName, isSystemName,
22                           nameOccName, nameModule, setNameModule,
23                           pprOccName, isLocallyDefined, nameUnique, nameOccName,
24                           setNameProvenance, getNameProvenance, pprNameProvenance
25                         )
26 import NameSet
27 import OccName          ( OccName,
28                           mkDFunOcc, 
29                           occNameFlavour, moduleIfaceFlavour
30                         )
31 import TyCon            ( TyCon )
32 import FiniteMap
33 import Unique           ( Unique, Uniquable(..), unboundKey )
34 import UniqFM           ( emptyUFM, listToUFM, plusUFM_C )
35 import UniqSupply
36 import SrcLoc           ( SrcLoc, noSrcLoc )
37 import Outputable
38 import Util             ( removeDups, equivClasses, thenCmp )
39 import List             ( nub )
40 import Maybes           ( mapMaybe )
41 import Char             ( isAlphanum )
42 \end{code}
43
44
45
46 %*********************************************************
47 %*                                                      *
48 \subsection{Making new names}
49 %*                                                      *
50 %*********************************************************
51
52 \begin{code}
53 newImportedGlobalName :: Module -> OccName
54                       -> RnM s d Name
55 newImportedGlobalName mod occ
56   =     -- First check the cache
57     getNameSupplyRn             `thenRn` \ (us, inst_ns, cache) ->
58     let 
59         key     = (mod,occ)
60         mod_hif = moduleIfaceFlavour mod
61     in
62     case lookupFM cache key of
63         
64         -- A hit in the cache!
65         -- Make sure that the module in the name has the same IfaceFlavour as
66         -- the module we are looking for; if not, make it so
67         -- so that it has the right HiFlag component.
68         -- (This is necessary for known-key things.  
69         --      For example, GHCmain.lhs imports as SOURCE
70         --      Main; but Main.main is a known-key thing.)  
71         Just name | isSystemName name   -- A known-key name; fix the provenance and module
72                   -> getOmitQualFn                      `thenRn` \ omit_fn ->
73                      let
74                           new_name = fixupSystemName name mod (NonLocalDef ImplicitImport (omit_fn name))
75                           new_cache = addToFM cache key new_name
76                      in
77                      setNameSupplyRn (us, inst_ns, new_cache)   `thenRn_`
78                      returnRn new_name
79
80                   | otherwise
81                   -> returnRn name
82                      
83         Nothing ->      -- Miss in the cache!
84                         -- Build a new original name, and put it in the cache
85                    getOmitQualFn                        `thenRn` \ omit_fn ->
86                    let
87                         (us', us1) = splitUniqSupply us
88                         uniq       = uniqFromSupply us1
89                         name       = mkGlobalName uniq mod occ (NonLocalDef ImplicitImport (omit_fn name))
90                                         -- For in-scope things we improve the provenance
91                                         -- in RnNames.importsFromImportDecl
92                         new_cache  = addToFM cache key name
93                    in
94                    setNameSupplyRn (us', inst_ns, new_cache)            `thenRn_`
95                    returnRn name
96
97
98 newImportedGlobalFromRdrName rdr_name
99   | isQual rdr_name
100   = newImportedGlobalName (rdrNameModule rdr_name) (rdrNameOcc rdr_name)
101
102   | otherwise
103   =     -- An Unqual is allowed; interface files contain 
104         -- unqualified names for locally-defined things, such as
105         -- constructors of a data type.
106     getModuleRn         `thenRn ` \ mod_name ->
107     newImportedGlobalName mod_name (rdrNameOcc rdr_name)
108
109
110 newLocallyDefinedGlobalName :: Module -> OccName 
111                             -> (Name -> ExportFlag) -> SrcLoc
112                             -> RnM s d Name
113 newLocallyDefinedGlobalName mod occ rec_exp_fn loc
114   =     -- First check the cache
115     getNameSupplyRn             `thenRn` \ (us, inst_ns, cache) ->
116     let 
117         key          = (mod,occ)
118         mk_prov name = LocalDef loc (rec_exp_fn name)
119         -- We must set the provenance of the thing in the cache
120         -- correctly, particularly whether or not it is locally defined.
121         --
122         -- Since newLocallyDefinedGlobalName is used only
123         -- at binding occurrences, we may as well get the provenance
124         -- dead right first time; hence the rec_exp_fn passed in
125     in
126     case lookupFM cache key of
127
128         -- A hit in the cache!
129         -- Overwrite whatever provenance is in the cache already; 
130         -- this updates WiredIn things and known-key things, 
131         -- which are there from the start, to LocalDef.
132         --
133         -- It also means that if there are two defns for the same thing
134         -- in a module, then each gets a separate SrcLoc
135         Just name -> let 
136                         new_name = setNameProvenance name (mk_prov new_name)
137                         new_cache = addToFM cache key new_name
138                      in
139                      setNameSupplyRn (us, inst_ns, new_cache)           `thenRn_`
140                      returnRn new_name
141                      
142         -- Miss in the cache!
143         -- Build a new original name, and put it in the cache
144         Nothing -> let
145                         (us', us1) = splitUniqSupply us
146                         uniq       = uniqFromSupply us1
147                         new_name   = mkGlobalName uniq mod occ (mk_prov new_name)
148                         new_cache  = addToFM cache key new_name
149                    in
150                    setNameSupplyRn (us', inst_ns, new_cache)            `thenRn_`
151                    returnRn new_name
152
153
154 newLocalNames :: [(RdrName,SrcLoc)] -> RnM s d [Name]
155 newLocalNames rdr_names
156   = getNameSupplyRn             `thenRn` \ (us, inst_ns, cache) ->
157     let
158         n          = length rdr_names
159         (us', us1) = splitUniqSupply us
160         uniqs      = uniqsFromSupply n us1
161         locals     = [ mkLocalName uniq (rdrNameOcc rdr_name) loc
162                      | ((rdr_name,loc), uniq) <- rdr_names `zip` uniqs
163                      ]
164     in
165     setNameSupplyRn (us', inst_ns, cache)       `thenRn_`
166     returnRn locals
167
168 newDFunName cl_occ tycon_occ (Just n) src_loc           -- Imported ones have "Just n"
169   = newImportedGlobalFromRdrName n
170
171 newDFunName cl_occ tycon_occ Nothing src_loc            -- Local instance decls have a "Nothing"
172   = getModuleRn                         `thenRn` \ mod_name ->
173     newInstUniq (cl_occ, tycon_occ)     `thenRn` \ inst_uniq ->
174     let
175         dfun_occ = mkDFunOcc cl_occ tycon_occ inst_uniq
176     in
177     newLocallyDefinedGlobalName mod_name dfun_occ (\_ -> Exported) src_loc
178
179
180 -- mkUnboundName makes a place-holder Name; it shouldn't be looked at except possibly
181 -- during compiler debugging.
182 mkUnboundName :: RdrName -> Name
183 mkUnboundName rdr_name = mkLocalName unboundKey (rdrNameOcc rdr_name) noSrcLoc
184
185 isUnboundName :: Name -> Bool
186 isUnboundName name = getUnique name == unboundKey
187 \end{code}
188
189 \begin{code}
190 -------------------------------------
191 bindLocatedLocalsRn :: SDoc                     -- Documentation string for error message
192                     -> [(RdrName,SrcLoc)]
193                     -> ([Name] -> RnMS s a)
194                     -> RnMS s a
195 bindLocatedLocalsRn doc_str rdr_names_w_loc enclosed_scope
196   = checkDupOrQualNames doc_str rdr_names_w_loc `thenRn_`
197
198     getLocalNameEnv                     `thenRn` \ name_env ->
199     (if opt_WarnNameShadowing
200      then
201         mapRn (check_shadow name_env) rdr_names_w_loc
202      else
203         returnRn []
204     )                                   `thenRn_`
205         
206     newLocalNames rdr_names_w_loc       `thenRn` \ names ->
207     let
208         new_name_env = addListToRdrEnv name_env (map fst rdr_names_w_loc `zip` names)
209     in
210     setLocalNameEnv new_name_env (enclosed_scope names)
211   where
212     check_shadow name_env (rdr_name,loc)
213         = case lookupRdrEnv name_env rdr_name of
214                 Nothing   -> returnRn ()
215                 Just name -> pushSrcLocRn loc $
216                              addWarnRn (shadowedNameWarn rdr_name)
217
218
219 -------------------------------------
220 bindLocalsRn doc_str rdr_names enclosed_scope
221   = getSrcLocRn         `thenRn` \ loc ->
222     bindLocatedLocalsRn (text doc_str)
223                         (rdr_names `zip` repeat loc)
224                         enclosed_scope
225
226         -- binLocalsFVRn is the same as bindLocalsRn
227         -- except that it deals with free vars
228 bindLocalsFVRn doc_str rdr_names enclosed_scope
229   = bindLocalsRn doc_str rdr_names      $ \ names ->
230     enclosed_scope names                `thenRn` \ (thing, fvs) ->
231     returnRn (thing, delListFromNameSet fvs names)
232
233 -------------------------------------
234 extendTyVarEnvFVRn :: [HsTyVar Name] -> RnMS s (a, FreeVars) -> RnMS s (a, FreeVars)
235         -- This tiresome function is used only in rnDecl on InstDecl
236 extendTyVarEnvFVRn tyvars enclosed_scope
237   = getLocalNameEnv             `thenRn` \ env ->
238     let
239         tyvar_names = map getTyVarName tyvars
240         new_env = addListToRdrEnv env [ (mkRdrUnqual (getOccName name), name) 
241                                       | name <- tyvar_names
242                                       ]
243     in
244     setLocalNameEnv new_env enclosed_scope      `thenRn` \ (thing, fvs) -> 
245     returnRn (thing, delListFromNameSet fvs tyvar_names)
246
247 bindTyVarsRn :: SDoc -> [HsTyVar RdrName]
248               -> ([HsTyVar Name] -> RnMS s a)
249               -> RnMS s a
250 bindTyVarsRn doc_str tyvar_names enclosed_scope
251   = bindTyVars2Rn doc_str tyvar_names   $ \ names tyvars ->
252     enclosed_scope tyvars
253
254 -- Gruesome name: return Names as well as HsTyVars
255 bindTyVars2Rn :: SDoc -> [HsTyVar RdrName]
256               -> ([Name] -> [HsTyVar Name] -> RnMS s a)
257               -> RnMS s a
258 bindTyVars2Rn doc_str tyvar_names enclosed_scope
259   = getSrcLocRn                                 `thenRn` \ loc ->
260     let
261         located_tyvars = [(getTyVarName tv, loc) | tv <- tyvar_names] 
262     in
263     bindLocatedLocalsRn doc_str located_tyvars  $ \ names ->
264     enclosed_scope names (zipWith replaceTyVarName tyvar_names names)
265
266 bindTyVarsFVRn :: SDoc -> [HsTyVar RdrName]
267               -> ([HsTyVar Name] -> RnMS s (a, FreeVars))
268               -> RnMS s (a, FreeVars)
269 bindTyVarsFVRn doc_str rdr_names enclosed_scope
270   = bindTyVars2Rn doc_str rdr_names     $ \ names tyvars ->
271     enclosed_scope tyvars               `thenRn` \ (thing, fvs) ->
272     returnRn (thing, delListFromNameSet fvs names)
273
274 bindTyVarsFV2Rn :: SDoc -> [HsTyVar RdrName]
275               -> ([Name] -> [HsTyVar Name] -> RnMS s (a, FreeVars))
276               -> RnMS s (a, FreeVars)
277 bindTyVarsFV2Rn doc_str rdr_names enclosed_scope
278   = bindTyVars2Rn doc_str rdr_names     $ \ names tyvars ->
279     enclosed_scope names tyvars         `thenRn` \ (thing, fvs) ->
280     returnRn (thing, delListFromNameSet fvs names)
281
282
283 -------------------------------------
284 checkDupOrQualNames, checkDupNames :: SDoc
285                                    -> [(RdrName, SrcLoc)]
286                                    -> RnM s d ()
287         -- Works in any variant of the renamer monad
288
289 checkDupOrQualNames doc_str rdr_names_w_loc
290   =     -- Check for use of qualified names
291     mapRn (qualNameErr doc_str) quals   `thenRn_`
292     checkDupNames doc_str rdr_names_w_loc
293   where
294     quals = filter (isQual.fst) rdr_names_w_loc
295     
296 checkDupNames doc_str rdr_names_w_loc
297   =     -- Check for dupicated names in a binding group
298     mapRn (dupNamesErr doc_str) dups    `thenRn_`
299     returnRn ()
300   where
301     (_, dups) = removeDups (\(n1,l1) (n2,l2) -> n1 `compare` n2) rdr_names_w_loc
302 \end{code}
303
304
305 %*********************************************************
306 %*                                                      *
307 \subsection{Looking up names}
308 %*                                                      *
309 %*********************************************************
310
311 Looking up a name in the RnEnv.
312
313 \begin{code}
314 lookupBndrRn rdr_name
315   = getNameEnvs         `thenRn` \ (global_env, local_env) ->
316
317         -- Try local env
318     case lookupRdrEnv local_env rdr_name of {
319           Just name -> returnRn name ;
320           Nothing   ->
321
322     getModeRn   `thenRn` \ mode ->
323     case mode of 
324         InterfaceMode _ ->      -- Look in the global name cache
325                             newImportedGlobalFromRdrName rdr_name
326
327         SourceMode      ->      -- Source mode, so look up a *qualified* version
328                                 -- of the name, so that we get the right one even
329                                 -- if there are many with the same occ name
330                                 -- There must *be* a binding
331                             getModuleRn         `thenRn` \ mod ->
332                             case lookupRdrEnv global_env (qualifyRdrName mod rdr_name) of
333                                 Just (name:rest) -> ASSERT( null rest )
334                                                     returnRn name 
335                                 Nothing          -> pprPanic "lookupBndrRn" (ppr mod <+> ppr rdr_name)
336     }
337
338 -- Just like lookupRn except that we record the occurrence too
339 -- Perhaps surprisingly, even wired-in names are recorded.
340 -- Why?  So that we know which wired-in names are referred to when
341 -- deciding which instance declarations to import.
342 lookupOccRn :: RdrName -> RnMS s Name
343 lookupOccRn rdr_name
344   = getNameEnvs                                 `thenRn` \ (global_env, local_env) ->
345     lookup_occ global_env local_env rdr_name    `thenRn` \ name ->
346     addOccurrenceName name
347
348 -- lookupGlobalOccRn is like lookupOccRn, except that it looks in the global 
349 -- environment.  It's used only for
350 --      record field names
351 --      class op names in class and instance decls
352 lookupGlobalOccRn :: RdrName -> RnMS s Name
353 lookupGlobalOccRn rdr_name
354   = getNameEnvs                                 `thenRn` \ (global_env, local_env) ->
355     lookup_global_occ global_env rdr_name       `thenRn` \ name ->
356     addOccurrenceName name
357
358 -- Look in both local and global env
359 lookup_occ global_env local_env rdr_name
360   = case lookupRdrEnv local_env rdr_name of
361           Just name -> returnRn name
362           Nothing   -> lookup_global_occ global_env rdr_name
363
364 -- Look in global env only
365 lookup_global_occ global_env rdr_name
366   = case lookupRdrEnv global_env rdr_name of
367         Just [name]         -> returnRn name
368         Just stuff@(name:_) -> addNameClashErrRn rdr_name stuff `thenRn_`
369                                returnRn name
370         Nothing -> getModeRn    `thenRn` \ mode ->
371                    case mode of 
372                         -- Not found when processing source code; so fail
373                         SourceMode    -> failWithRn (mkUnboundName rdr_name)
374                                                     (unknownNameErr rdr_name)
375                 
376                         -- Not found when processing an imported declaration,
377                         -- so we create a new name for the purpose
378                         InterfaceMode _ -> newImportedGlobalFromRdrName rdr_name
379
380   
381 -- lookupImplicitOccRn takes an RdrName representing an *original* name, and
382 -- adds it to the occurrence pool so that it'll be loaded later.  This is
383 -- used when language constructs (such as monad comprehensions, overloaded literals,
384 -- or deriving clauses) require some stuff to be loaded that isn't explicitly
385 -- mentioned in the code.
386 --
387 -- This doesn't apply in interface mode, where everything is explicit, but
388 -- we don't check for this case: it does no harm to record an "extra" occurrence
389 -- and lookupImplicitOccRn isn't used much in interface mode (it's only the
390 -- Nothing clause of rnDerivs that calls it at all I think).
391 --      [Jan 98: this comment is wrong: rnHsType uses it quite a bit.]
392 --
393 -- For List and Tuple types it's important to get the correct
394 -- isLocallyDefined flag, which is used in turn when deciding
395 -- whether there are any instance decls in this module are "special".
396 -- The name cache should have the correct provenance, though.
397
398 lookupImplicitOccRn :: RdrName -> RnMS s Name 
399 lookupImplicitOccRn rdr_name
400  = newImportedGlobalFromRdrName rdr_name        `thenRn` \ name ->
401    addOccurrenceName name
402
403 addImplicitOccRn :: Name -> RnMS s Name
404 addImplicitOccRn name = addOccurrenceName name
405
406 addImplicitOccsRn :: [Name] -> RnMS s ()
407 addImplicitOccsRn names = addOccurrenceNames names
408 \end{code}
409
410 \begin{code}
411 lookupFixity :: Name -> RnMS s Fixity
412 lookupFixity name
413   = getFixityEnv        `thenRn` \ fixity_env ->
414     case lookupNameEnv fixity_env name of
415         Just (FixitySig _ fixity _) -> returnRn fixity
416         Nothing                     -> returnRn (Fixity 9 InfixL)       -- Default case
417 \end{code}
418
419 unQualInScope returns a function that takes a Name and tells whether
420 its unqualified name is in scope.  This is put as a boolean flag in
421 the Name's provenance to guide whether or not to print the name qualified
422 in error messages.
423
424 \begin{code}
425 unQualInScope :: GlobalRdrEnv -> Name -> Bool
426 unQualInScope env
427   = lookup
428   where
429     lookup name = case lookupRdrEnv env (mkRdrUnqual (nameOccName name)) of
430                            Just [name'] -> name == name'
431                            other        -> False
432 \end{code}
433
434 %************************************************************************
435 %*                                                                      *
436 \subsection{Envt utility functions}
437 %*                                                                      *
438 %************************************************************************
439
440 ===============  RnEnv  ================
441 \begin{code}
442 plusRnEnv (RnEnv n1 f1) (RnEnv n2 f2) 
443   = RnEnv (n1 `plusGlobalRdrEnv` n2)
444           (f1 `plusNameEnv`     f2)
445 \end{code}
446
447
448 ===============  NameEnv  ================
449 \begin{code}
450 plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
451 plusGlobalRdrEnv env1 env2 = plusFM_C combine_globals env1 env2
452
453 addOneToGlobalRdrEnv :: GlobalRdrEnv -> RdrName -> Name -> GlobalRdrEnv
454 addOneToGlobalRdrEnv env rdr_name name = addToFM_C combine_globals env rdr_name [name]
455
456 delOneFromGlobalRdrEnv :: GlobalRdrEnv -> RdrName -> GlobalRdrEnv 
457 delOneFromGlobalRdrEnv env rdr_name = delFromFM env rdr_name
458
459 combine_globals :: [Name]       -- Old
460                 -> [Name]       -- New
461                 -> [Name]
462 combine_globals ns_old ns_new   -- ns_new is often short
463   = foldr add ns_old ns_new
464   where
465     add n ns | all (no_conflict n) ns_old = map choose ns       -- Eliminate duplicates
466              | otherwise                  = n:ns
467              where
468                choose n' | n==n' && better_provenance n n' = n
469                          | otherwise                       = n'
470
471 -- Choose 
472 --      a local thing                 over an   imported thing
473 --      a user-imported thing         over a    non-user-imported thing
474 --      an explicitly-imported thing  over an   implicitly imported thing
475 better_provenance n1 n2
476   = case (getNameProvenance n1, getNameProvenance n2) of
477         (LocalDef _ _,                        _                           ) -> True
478         (NonLocalDef (UserImport _ _ True) _, _                           ) -> True
479         (NonLocalDef (UserImport _ _ _   ) _, NonLocalDef ImplicitImport _) -> True
480         other                                                               -> False
481
482 no_conflict :: Name -> Name -> Bool
483 no_conflict n1 n2 | isLocallyDefined n1 && isLocallyDefined n2 = False
484                   | otherwise                                  = n1 == n2
485         -- We complain of a conflict if one RdrName maps to two different Names,
486         -- OR if one RdrName maps to the same *locally-defined* Name.  The latter
487         -- case is to catch two separate, local definitions of the same thing.
488         --
489         -- If a module imports itself then there might be a local defn and an imported
490         -- defn of the same name; in this case the names will compare as equal, but
491         -- will still have different provenances
492 \end{code}
493
494
495
496 ===============  ExportAvails  ================
497 \begin{code}
498 mkEmptyExportAvails :: Module -> ExportAvails
499 mkEmptyExportAvails mod_name = (unitFM mod_name [], emptyUFM)
500
501 mkExportAvails :: Module -> Bool -> GlobalRdrEnv -> [AvailInfo] -> ExportAvails
502 mkExportAvails mod_name unqual_imp name_env avails
503   = (mod_avail_env, entity_avail_env)
504   where
505     mod_avail_env = unitFM mod_name unqual_avails 
506
507         -- unqual_avails is the Avails that are visible in *unqualfied* form
508         -- (1.4 Report, Section 5.1.1)
509         -- For example, in 
510         --      import T hiding( f )
511         -- we delete f from avails
512
513     unqual_avails | not unqual_imp = [] -- Short cut when no unqualified imports
514                   | otherwise      = mapMaybe prune avails
515
516     prune (Avail n) | unqual_in_scope n = Just (Avail n)
517     prune (Avail n) | otherwise         = Nothing
518     prune (AvailTC n ns) | null uqs     = Nothing
519                          | otherwise    = Just (AvailTC n uqs)
520                          where
521                            uqs = filter unqual_in_scope ns
522
523     unqual_in_scope n = unQualInScope name_env n
524
525     entity_avail_env = listToUFM [ (name,avail) | avail <- avails, 
526                                                   name  <- availNames avail]
527
528 plusExportAvails ::  ExportAvails ->  ExportAvails ->  ExportAvails
529 plusExportAvails (m1, e1) (m2, e2)
530   = (plusFM_C (++) m1 m2, plusUFM_C plusAvail e1 e2)
531         -- ToDo: wasteful: we do this once for each constructor!
532 \end{code}
533
534
535 ===============  AvailInfo  ================
536 \begin{code}
537 plusAvail (Avail n1)       (Avail n2)       = Avail n1
538 plusAvail (AvailTC n1 ns1) (AvailTC n2 ns2) = AvailTC n1 (nub (ns1 ++ ns2))
539 -- Added SOF 4/97
540 #ifdef DEBUG
541 plusAvail a1 a2 = pprPanic "RnEnv.plusAvail" (hsep [pprAvail a1,pprAvail a2])
542 #endif
543
544 addAvailToNameSet :: NameSet -> AvailInfo -> NameSet
545 addAvailToNameSet names avail = addListToNameSet names (availNames avail)
546
547 availsToNameSet :: [AvailInfo] -> NameSet
548 availsToNameSet avails = foldl addAvailToNameSet emptyNameSet avails
549
550 availName :: AvailInfo -> Name
551 availName (Avail n)     = n
552 availName (AvailTC n _) = n
553
554 availNames :: AvailInfo -> [Name]
555 availNames (Avail n)      = [n]
556 availNames (AvailTC n ns) = ns
557
558 filterAvail :: RdrNameIE        -- Wanted
559             -> AvailInfo        -- Available
560             -> Maybe AvailInfo  -- Resulting available; 
561                                 -- Nothing if (any of the) wanted stuff isn't there
562
563 filterAvail ie@(IEThingWith want wants) avail@(AvailTC n ns)
564   | sub_names_ok = Just (AvailTC n (filter is_wanted ns))
565   | otherwise    = Nothing
566   where
567     is_wanted name = nameOccName name `elem` wanted_occs
568     sub_names_ok   = all (`elem` avail_occs) wanted_occs
569     avail_occs     = map nameOccName ns
570     wanted_occs    = map rdrNameOcc (want:wants)
571
572 filterAvail (IEThingAbs _) (AvailTC n ns)       = ASSERT( n `elem` ns ) 
573                                                   Just (AvailTC n [n])
574
575 filterAvail (IEThingAbs _) avail@(Avail n)      = Just avail            -- Type synonyms
576
577 filterAvail (IEVar _)      avail@(Avail n)      = Just avail
578 filterAvail (IEVar v)      avail@(AvailTC n ns) = Just (AvailTC n (filter wanted ns))
579                                                 where
580                                                   wanted n = nameOccName n == occ
581                                                   occ      = rdrNameOcc v
582         -- The second equation happens if we import a class op, thus
583         --      import A( op ) 
584         -- where op is a class operation
585
586 filterAvail (IEThingAll _) avail@(AvailTC _ _)  = Just avail
587
588 filterAvail ie avail = Nothing
589
590
591 -- In interfaces, pprAvail gets given the OccName of the "host" thing
592 pprAvail avail = getPprStyle $ \ sty ->
593                  if ifaceStyle sty then
594                     ppr_avail (pprOccName . nameOccName) avail
595                  else
596                     ppr_avail ppr avail
597
598 ppr_avail pp_name (AvailTC n ns) = hsep [
599                                      pp_name n,
600                                      parens  $ hsep $ punctuate comma $
601                                      map pp_name ns
602                                    ]
603 ppr_avail pp_name (Avail n) = pp_name n
604 \end{code}
605
606
607
608
609 %************************************************************************
610 %*                                                                      *
611 \subsection{Free variable manipulation}
612 %*                                                                      *
613 %************************************************************************
614
615 \begin{code}
616 type FreeVars   = NameSet
617
618 plusFV   :: FreeVars -> FreeVars -> FreeVars
619 addOneFV :: FreeVars -> Name -> FreeVars
620 unitFV   :: Name -> FreeVars
621 emptyFVs :: FreeVars
622 plusFVs  :: [FreeVars] -> FreeVars
623
624 emptyFVs  = emptyNameSet
625 plusFVs   = unionManyNameSets
626 plusFV    = unionNameSets
627
628 -- No point in adding implicitly imported names to the free-var set
629 addOneFV s n = addOneToNameSet s n
630 unitFV     n = unitNameSet n
631 \end{code}
632
633
634 %************************************************************************
635 %*                                                                      *
636 \subsection{Envt utility functions}
637 %*                                                                      *
638 %************************************************************************
639
640
641 \begin{code}
642 warnUnusedLocalBinds, warnUnusedTopNames, warnUnusedMatches :: [Name] -> RnM s d ()
643
644 warnUnusedTopNames names
645   | not opt_WarnUnusedBinds && not opt_WarnUnusedImports = returnRn ()  -- Don't force ns unless necessary
646   | otherwise                                            = warnUnusedBinds names
647
648 warnUnusedLocalBinds ns
649   | not opt_WarnUnusedBinds = returnRn ()
650   | otherwise               = warnUnusedBinds ns
651
652 warnUnusedMatches names
653   | opt_WarnUnusedMatches = warnUnusedGroup names
654   | otherwise             = returnRn ()
655
656 -------------------------
657
658 warnUnusedBinds :: [Name] -> RnM s d ()
659 warnUnusedBinds names
660   = mapRn warnUnusedGroup groups        `thenRn_`
661     returnRn ()
662   where
663         -- Group by provenance
664    groups = equivClasses cmp names
665    name1 `cmp` name2 = getNameProvenance name1 `cmp_prov` getNameProvenance name2
666  
667    cmp_prov (LocalDef _ _) (NonLocalDef _ _)       = LT
668    cmp_prov (LocalDef loc1 _) (LocalDef loc2 _)    = loc1 `compare` loc2
669    cmp_prov (NonLocalDef (UserImport m1 loc1 _) _)
670             (NonLocalDef (UserImport m2 loc2 _) _) = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
671    cmp_prov (NonLocalDef _ _) (LocalDef _ _)       = GT
672                         -- In-scope NonLocalDefs must have UserImport info on them
673
674 -------------------------
675
676 warnUnusedGroup :: [Name] -> RnM s d ()
677 warnUnusedGroup []
678   = returnRn ()
679
680 warnUnusedGroup names
681   | is_local     && not opt_WarnUnusedBinds   = returnRn ()
682   | not is_local && not opt_WarnUnusedImports = returnRn ()
683   | otherwise
684   = pushSrcLocRn def_loc        $
685     addWarnRn                   $
686     sep [msg <> colon, nest 4 (fsep (punctuate comma (map ppr names)))]
687   where
688     name1 = head names
689     (is_local, def_loc, msg)
690         = case getNameProvenance name1 of
691                 LocalDef loc _                       -> (True, loc, text "Defined but not used")
692                 NonLocalDef (UserImport mod loc _) _ -> (True, loc, text "Imported from" <+> quotes (ppr mod) <+> 
693                                                                      text "but but not used")
694                 other -> (False, getSrcLoc name1, text "Strangely defined but not used")
695 \end{code}
696
697 \begin{code}
698 addNameClashErrRn rdr_name (name1:names)
699   = addErrRn (vcat [ptext SLIT("Ambiguous occurrence") <+> quotes (ppr rdr_name),
700                     ptext SLIT("It could refer to") <+> vcat (msg1 : msgs)])
701   where
702     msg1 = ptext  SLIT("either") <+> mk_ref name1
703     msgs = [ptext SLIT("    or") <+> mk_ref name | name <- names]
704     mk_ref name = quotes (ppr name) <> comma <+> pprNameProvenance name
705
706 fixityClashErr (rdr_name, ((_,how_in_scope1), (_, how_in_scope2)))
707   = hang (hsep [ptext SLIT("Conflicting fixities for"), quotes (ppr rdr_name)])
708         4 (vcat [ppr how_in_scope1,
709                  ppr how_in_scope2])
710
711 shadowedNameWarn shadow
712   = hsep [ptext SLIT("This binding for"), 
713                quotes (ppr shadow),
714                ptext SLIT("shadows an existing binding")]
715
716 unknownNameErr name
717   = sep [text flavour, ptext SLIT("not in scope:"), quotes (ppr name)]
718   where
719     flavour = occNameFlavour (rdrNameOcc name)
720
721 qualNameErr descriptor (name,loc)
722   = pushSrcLocRn loc $
723     addErrRn (hsep [ ptext SLIT("Invalid use of qualified name"), 
724                      quotes (ppr name),
725                      ptext SLIT("in"),
726                      descriptor])
727
728 dupNamesErr descriptor ((name,loc) : dup_things)
729   = pushSrcLocRn loc $
730     addErrRn ((ptext SLIT("Conflicting definitions for") <+> quotes (ppr name))
731               $$ 
732               (ptext SLIT("in") <+> descriptor))
733 \end{code}
734