[project @ 2001-03-14 15:26:00 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 module HscTypes ( 
8         ModuleLocation(..),
9
10         ModDetails(..), ModIface(..), 
11         HomeSymbolTable, emptySymbolTable,
12         PackageTypeEnv,
13         HomeIfaceTable, PackageIfaceTable, emptyIfaceTable,
14         lookupIface, lookupIfaceByModName,
15         emptyModIface,
16
17         InteractiveContext(..),
18
19         IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts,
20
21         VersionInfo(..), initialVersionInfo, lookupVersion,
22
23         TyThing(..), isTyClThing, implicitTyThingIds,
24
25         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
26         extendTypeEnvList, extendTypeEnvWithIds,
27         typeEnvClasses, typeEnvTyCons, typeEnvIds,
28
29         ImportedModuleInfo, WhetherHasOrphans, ImportVersion, WhatsImported(..),
30         PersistentRenamerState(..), IsBootInterface, DeclsMap,
31         IfaceInsts, IfaceRules, GatedDecl, GatedDecls, IsExported,
32         NameSupply(..), OrigNameCache, OrigIParamCache,
33         Avails, AvailEnv, GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
34         PersistentCompilerState(..),
35
36         Deprecations(..), lookupDeprec,
37
38         InstEnv, ClsInstEnv, DFunId,
39         PackageInstEnv, PackageRuleBase,
40
41         GlobalRdrEnv, GlobalRdrElt(..), pprGlobalRdrEnv,
42         LocalRdrEnv, extendLocalRdrEnv,
43         
44
45         -- Provenance
46         Provenance(..), ImportReason(..), 
47         pprNameProvenance, hasBetterProv
48
49     ) where
50
51 #include "HsVersions.h"
52
53 import RdrName          ( RdrNameEnv, addListToRdrEnv, emptyRdrEnv, mkRdrUnqual, rdrEnvToList )
54 import Name             ( Name, NamedThing, getName, nameOccName, nameModule, nameSrcLoc )
55 import NameEnv
56 import OccName          ( OccName )
57 import Module           ( Module, ModuleName, ModuleEnv,
58                           lookupModuleEnv, lookupModuleEnvByName, emptyModuleEnv
59                         )
60 import InstEnv          ( InstEnv, ClsInstEnv, DFunId )
61 import Rules            ( RuleBase )
62 import CoreSyn          ( CoreBind )
63 import Id               ( Id )
64 import Class            ( Class, classSelIds )
65 import TyCon            ( TyCon, tyConGenIds, tyConSelIds, tyConDataConsIfAvailable )
66 import DataCon          ( dataConId, dataConWrapId )
67
68 import BasicTypes       ( Version, initialVersion, Fixity )
69
70 import HsSyn            ( DeprecTxt, tyClDeclName, ifaceRuleDeclName )
71 import RdrHsSyn         ( RdrNameInstDecl, RdrNameRuleDecl, RdrNameTyClDecl )
72 import RnHsSyn          ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
73
74 import CoreSyn          ( IdCoreRule )
75
76 import FiniteMap        ( FiniteMap )
77 import Bag              ( Bag )
78 import Maybes           ( seqMaybe, orElse )
79 import Outputable
80 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
81 import Util             ( thenCmp, sortLt )
82 import UniqSupply       ( UniqSupply )
83 \end{code}
84
85 %************************************************************************
86 %*                                                                      *
87 \subsection{Module locations}
88 %*                                                                      *
89 %************************************************************************
90
91 \begin{code}
92 data ModuleLocation
93    = ModuleLocation {
94         ml_hs_file   :: Maybe FilePath,
95         ml_hspp_file :: Maybe FilePath,  -- path of preprocessed source
96         ml_hi_file   :: Maybe FilePath,
97         ml_obj_file  :: Maybe FilePath
98      }
99      deriving Show
100
101 instance Outputable ModuleLocation where
102    ppr = text . show
103 \end{code}
104
105 For a module in another package, the hs_file and obj_file
106 components of ModuleLocation are undefined.  
107
108 The locations specified by a ModuleLocation may or may not
109 correspond to actual files yet: for example, even if the object
110 file doesn't exist, the ModuleLocation still contains the path to
111 where the object file will reside if/when it is created.
112
113
114 %************************************************************************
115 %*                                                                      *
116 \subsection{Symbol tables and Module details}
117 %*                                                                      *
118 %************************************************************************
119
120 A @ModIface@ plus a @ModDetails@ summarises everything we know 
121 about a compiled module.  The @ModIface@ is the stuff *before* linking,
122 and can be written out to an interface file.  The @ModDetails@ is after
123 linking; it is the "linked" form of the mi_decls field.
124
125 \begin{code}
126 data ModIface 
127    = ModIface {
128         mi_module   :: Module,                  -- Complete with package info
129         mi_version  :: VersionInfo,             -- Module version number
130         mi_orphan   :: WhetherHasOrphans,       -- Whether this module has orphans
131         mi_boot     :: IsBootInterface,         -- Whether this interface was read from an hi-boot file
132
133         mi_usages   :: [ImportVersion Name],    -- Usages; kept sorted so that it's easy
134                                                 -- to decide whether to write a new iface file
135                                                 -- (changing usages doesn't affect the version of
136                                                 --  this module)
137
138         mi_exports  :: [(ModuleName,Avails)],   -- What it exports
139                                                 -- Kept sorted by (mod,occ),
140                                                 -- to make version comparisons easier
141
142         mi_globals  :: GlobalRdrEnv,            -- Its top level environment
143
144         mi_fixities :: NameEnv Fixity,          -- Fixities
145         mi_deprecs  :: Deprecations,            -- Deprecations
146
147         mi_decls    :: IfaceDecls               -- The RnDecls form of ModDetails
148      }
149
150 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl],  -- Sorted
151                                dcl_rules :: [RenamedRuleDecl],  -- Sorted
152                                dcl_insts :: [RenamedInstDecl] } -- Unsorted
153
154 mkIfaceDecls :: [RenamedTyClDecl] -> [RenamedRuleDecl] -> [RenamedInstDecl] -> IfaceDecls
155 mkIfaceDecls tycls rules insts
156   = IfaceDecls { dcl_tycl  = sortLt lt_tycl tycls,
157                  dcl_rules = sortLt lt_rule rules,
158                  dcl_insts = insts }
159   where
160     d1 `lt_tycl` d2 = tyClDeclName      d1 < tyClDeclName      d2
161     r1 `lt_rule` r2 = ifaceRuleDeclName r1 < ifaceRuleDeclName r2
162
163
164 -- typechecker should only look at this, not ModIface
165 -- Should be able to construct ModDetails from mi_decls in ModIface
166 data ModDetails
167    = ModDetails {
168         -- The next three fields are created by the typechecker
169         md_types    :: TypeEnv,
170         md_insts    :: [DFunId],        -- Dfun-ids for the instances in this module
171         md_rules    :: [IdCoreRule],    -- Domain may include Ids from other modules
172         md_binds    :: [CoreBind]
173      }
174
175 -- The ModDetails takes on several slightly different forms:
176 --
177 -- After typecheck + desugar
178 --      md_types        Contains TyCons, Classes, and hasNoBinding Ids
179 --      md_insts        All instances from this module (incl derived ones)
180 --      md_rules        All rules from this module
181 --      md_binds        Desugared bindings
182 --
183 -- After simplification
184 --      md_types        Same as after typecheck
185 --      md_insts        Ditto
186 --      md_rules        Orphan rules only (local ones now attached to binds)
187 --      md_binds        With rules attached
188 --
189 -- After CoreTidy
190 --      md_types        Now contains Ids as well, replete with final IdInfo
191 --                         The Ids are only the ones that are visible from
192 --                         importing modules.  Without -O that means only
193 --                         exported Ids, but with -O importing modules may
194 --                         see ids mentioned in unfoldings of exported Ids
195 --
196 --      md_insts        Same DFunIds as before, but with final IdInfo,
197 --                         and the unique might have changed; remember that
198 --                         CoreTidy links up the uniques of old and new versions
199 --
200 --      md_rules        All rules for exported things, substituted with final Ids
201 --
202 --      md_binds        Tidied
203 --
204 -- Passed back to compilation manager
205 --      Just as after CoreTidy, but with md_binds nuked
206
207 \end{code}
208
209 \begin{code}
210 emptyModDetails :: ModDetails
211 emptyModDetails
212   = ModDetails { md_types = emptyTypeEnv,
213                  md_insts = [],
214                  md_rules = []
215     }
216
217 emptyModIface :: Module -> ModIface
218 emptyModIface mod
219   = ModIface { mi_module   = mod,
220                mi_version  = initialVersionInfo,
221                mi_usages   = [],
222                mi_orphan   = False,
223                mi_boot     = False,
224                mi_exports  = [],
225                mi_fixities = emptyNameEnv,
226                mi_globals  = emptyRdrEnv,
227                mi_deprecs  = NoDeprecs,
228                mi_decls    = panic "emptyModIface: decls"
229     }           
230 \end{code}
231
232 Symbol tables map modules to ModDetails:
233
234 \begin{code}
235 type SymbolTable        = ModuleEnv ModDetails
236 type IfaceTable         = ModuleEnv ModIface
237
238 type HomeIfaceTable     = IfaceTable
239 type PackageIfaceTable  = IfaceTable
240
241 type HomeSymbolTable    = SymbolTable   -- Domain = modules in the home package
242
243 emptySymbolTable :: SymbolTable
244 emptySymbolTable = emptyModuleEnv
245
246 emptyIfaceTable :: IfaceTable
247 emptyIfaceTable = emptyModuleEnv
248 \end{code}
249
250 Simple lookups in the symbol table.
251
252 \begin{code}
253 lookupIface :: HomeIfaceTable -> PackageIfaceTable -> Name -> Maybe ModIface
254 -- We often have two IfaceTables, and want to do a lookup
255 lookupIface hit pit name
256   = lookupModuleEnv hit mod `seqMaybe` lookupModuleEnv pit mod
257   where
258     mod = nameModule name
259
260 lookupIfaceByModName :: HomeIfaceTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
261 -- We often have two IfaceTables, and want to do a lookup
262 lookupIfaceByModName hit pit mod
263   = lookupModuleEnvByName hit mod `seqMaybe` lookupModuleEnvByName pit mod
264 \end{code}
265
266
267 %************************************************************************
268 %*                                                                      *
269 \subsection{The interactive context}
270 %*                                                                      *
271 %************************************************************************
272
273 \begin{code}
274 data InteractiveContext 
275   = InteractiveContext { 
276         ic_module :: Module,            -- The current module in which 
277                                         -- the  user is sitting
278
279         ic_rn_env :: LocalRdrEnv,       -- Lexical context for variables bound
280                                         -- during interaction
281
282         ic_type_env :: TypeEnv          -- Ditto for types
283     }
284 \end{code}
285
286
287 %************************************************************************
288 %*                                                                      *
289 \subsection{Type environment stuff}
290 %*                                                                      *
291 %************************************************************************
292
293 \begin{code}
294 data TyThing = AnId   Id
295              | ATyCon TyCon
296              | AClass Class
297
298 isTyClThing :: TyThing -> Bool
299 isTyClThing (ATyCon _) = True
300 isTyClThing (AClass _) = True
301 isTyClThing (AnId   _) = False
302
303 instance NamedThing TyThing where
304   getName (AnId id)   = getName id
305   getName (ATyCon tc) = getName tc
306   getName (AClass cl) = getName cl
307
308 instance Outputable TyThing where
309   ppr (AnId   id) = ptext SLIT("AnId")   <+> ppr id
310   ppr (ATyCon tc) = ptext SLIT("ATyCon") <+> ppr tc
311   ppr (AClass cl) = ptext SLIT("AClass") <+> ppr cl
312
313 typeEnvClasses env = [cl | AClass cl <- nameEnvElts env]
314 typeEnvTyCons  env = [tc | ATyCon tc <- nameEnvElts env] 
315 typeEnvIds     env = [id | AnId id   <- nameEnvElts env] 
316
317 implicitTyThingIds :: [TyThing] -> [Id]
318 -- Add the implicit data cons and selectors etc 
319 implicitTyThingIds things
320   = concat (map go things)
321   where
322     go (AnId f)    = []
323     go (AClass cl) = classSelIds cl
324     go (ATyCon tc) = tyConGenIds tc ++
325                      tyConSelIds tc ++
326                      [ n | dc <- tyConDataConsIfAvailable tc, 
327                            n  <- [dataConId dc, dataConWrapId dc] ] 
328                 -- Synonyms return empty list of constructors and selectors
329 \end{code}
330
331
332 \begin{code}
333 type TypeEnv = NameEnv TyThing
334
335 emptyTypeEnv = emptyNameEnv
336
337 mkTypeEnv :: [TyThing] -> TypeEnv
338 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
339                 
340 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
341 extendTypeEnvList env things
342   = extendNameEnvList env [(getName thing, thing) | thing <- things]
343
344 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
345 extendTypeEnvWithIds env ids
346   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
347 \end{code}
348
349 \begin{code}
350 lookupType :: HomeSymbolTable -> PackageTypeEnv -> Name -> Maybe TyThing
351 lookupType hst pte name
352   = case lookupModuleEnv hst (nameModule name) of
353         Just details -> lookupNameEnv (md_types details) name
354         Nothing      -> lookupNameEnv pte name
355 \end{code}
356
357 %************************************************************************
358 %*                                                                      *
359 \subsection{Auxiliary types}
360 %*                                                                      *
361 %************************************************************************
362
363 These types are defined here because they are mentioned in ModDetails,
364 but they are mostly elaborated elsewhere
365
366 \begin{code}
367 data VersionInfo 
368   = VersionInfo {
369         vers_module  :: Version,        -- Changes when anything changes
370         vers_exports :: Version,        -- Changes when export list changes
371         vers_rules   :: Version,        -- Changes when any rule changes
372         vers_decls   :: NameEnv Version
373                 -- Versions for "big" names only (not data constructors, class ops)
374                 -- The version of an Id changes if its fixity changes
375                 -- Ditto data constructors, class operations, except that the version of
376                 -- the parent class/tycon changes
377                 --
378                 -- If a name isn't in the map, it means 'initialVersion'
379     }
380
381 initialVersionInfo :: VersionInfo
382 initialVersionInfo = VersionInfo { vers_module  = initialVersion,
383                                    vers_exports = initialVersion,
384                                    vers_rules   = initialVersion,
385                                    vers_decls   = emptyNameEnv
386                         }
387
388 lookupVersion :: NameEnv Version -> Name -> Version
389 lookupVersion env name = lookupNameEnv env name `orElse` initialVersion
390
391 data Deprecations = NoDeprecs
392                   | DeprecAll DeprecTxt                         -- Whole module deprecated
393                   | DeprecSome (NameEnv (Name,DeprecTxt))       -- Some things deprecated
394                                                                 -- Just "big" names
395                 -- We keep the Name in the range, so we can print them out
396
397 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
398 lookupDeprec NoDeprecs        name = Nothing
399 lookupDeprec (DeprecAll  txt) name = Just txt
400 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
401                                             Just (_, txt) -> Just txt
402                                             Nothing       -> Nothing
403
404 instance Eq Deprecations where
405   -- Used when checking whether we need write a new interface
406   NoDeprecs       == NoDeprecs       = True
407   (DeprecAll t1)  == (DeprecAll t2)  = t1 == t2
408   (DeprecSome e1) == (DeprecSome e2) = nameEnvElts e1 == nameEnvElts e2
409   d1              == d2              = False
410 \end{code}
411
412
413 \begin{code}
414 type Avails       = [AvailInfo]
415 type AvailInfo    = GenAvailInfo Name
416 type RdrAvailInfo = GenAvailInfo OccName
417
418 data GenAvailInfo name  = Avail name     -- An ordinary identifier
419                         | AvailTC name   -- The name of the type or class
420                                   [name] -- The available pieces of type/class.
421                                          -- NB: If the type or class is itself
422                                          -- to be in scope, it must be in this list.
423                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
424                         deriving( Eq )
425                         -- Equality used when deciding if the interface has changed
426
427 type AvailEnv     = NameEnv AvailInfo   -- Maps a Name to the AvailInfo that contains it
428                                 
429 instance Outputable n => Outputable (GenAvailInfo n) where
430    ppr = pprAvail
431
432 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
433 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
434                                         []  -> empty
435                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
436
437 pprAvail (Avail n) = ppr n
438 \end{code}
439
440
441 %************************************************************************
442 %*                                                                      *
443 \subsection{ModIface}
444 %*                                                                      *
445 %************************************************************************
446
447 \begin{code}
448 type WhetherHasOrphans   = Bool
449         -- An "orphan" is 
450         --      * an instance decl in a module other than the defn module for 
451         --              one of the tycons or classes in the instance head
452         --      * a transformation rule in a module other than the one defining
453         --              the function in the head of the rule.
454
455 type IsBootInterface     = Bool
456
457 type ImportVersion name  = (ModuleName, WhetherHasOrphans, IsBootInterface, WhatsImported name)
458
459 data WhatsImported name  = NothingAtAll                         -- The module is below us in the
460                                                                 -- hierarchy, but we import nothing
461
462                          | Everything Version           -- Used for modules from other packages;
463                                                         -- we record only the module's version number
464
465                          | Specifically 
466                                 Version                 -- Module version
467                                 (Maybe Version)         -- Export-list version, if we depend on it
468                                 [(name,Version)]        -- List guaranteed non-empty
469                                 Version                 -- Rules version
470
471                          deriving( Eq )
472         -- 'Specifically' doesn't let you say "I imported f but none of the rules in
473         -- the module". If you use anything in the module you get its rule version
474         -- So if the rules change, you'll recompile, even if you don't use them.
475         -- This is easy to implement, and it's safer: you might not have used the rules last
476         -- time round, but if someone has added a new rule you might need it this time
477
478         -- The export list field is (Just v) if we depend on the export list:
479         --      we imported the module without saying exactly what we imported
480         -- We need to recompile if the module exports changes, because we might
481         -- now have a name clash in the importing module.
482
483 type IsExported = Name -> Bool          -- True for names that are exported from this module
484 \end{code}
485
486
487 %************************************************************************
488 %*                                                                      *
489 \subsection{The persistent compiler state}
490 %*                                                                      *
491 %************************************************************************
492
493 \begin{code}
494 data PersistentCompilerState 
495    = PCS {
496         pcs_PIT :: PackageIfaceTable,   -- Domain = non-home-package modules
497                                         --   the mi_decls component is empty
498
499         pcs_PTE :: PackageTypeEnv,      -- Domain = non-home-package modules
500                                         --   except that the InstEnv components is empty
501
502         pcs_insts :: PackageInstEnv,    -- The total InstEnv accumulated from all
503                                         --   the non-home-package modules
504
505         pcs_rules :: PackageRuleBase,   -- Ditto RuleEnv
506
507         pcs_PRS :: PersistentRenamerState
508      }
509 \end{code}
510
511 The @PersistentRenamerState@ persists across successive calls to the
512 compiler.
513
514 It contains:
515   * A name supply, which deals with allocating unique names to
516     (Module,OccName) original names, 
517  
518   * An accumulated TypeEnv from all the modules in imported packages
519
520   * An accumulated InstEnv from all the modules in imported packages
521     The point is that we don't want to keep recreating it whenever
522     we compile a new module.  The InstEnv component of pcPST is empty.
523     (This means we might "see" instances that we shouldn't "really" see;
524     but the Haskell Report is vague on what is meant to be visible, 
525     so we just take the easy road here.)
526
527   * Ditto for rules
528
529   * A "holding pen" for declarations that have been read out of
530     interface files but not yet sucked in, renamed, and typechecked
531
532 \begin{code}
533 type PackageTypeEnv  = TypeEnv
534 type PackageRuleBase = RuleBase
535 type PackageInstEnv  = InstEnv
536
537 data PersistentRenamerState
538   = PRS { prsOrig    :: NameSupply,
539           prsImpMods :: ImportedModuleInfo,
540           prsDecls   :: DeclsMap,
541           prsInsts   :: IfaceInsts,
542           prsRules   :: IfaceRules
543     }
544 \end{code}
545
546 The NameSupply makes sure that there is just one Unique assigned for
547 each original name; i.e. (module-name, occ-name) pair.  The Name is
548 always stored as a Global, and has the SrcLoc of its binding location.
549 Actually that's not quite right.  When we first encounter the original
550 name, we might not be at its binding site (e.g. we are reading an
551 interface file); so we give it 'noSrcLoc' then.  Later, when we find
552 its binding site, we fix it up.
553
554 Exactly the same is true of the Module stored in the Name.  When we first
555 encounter the occurrence, we may not know the details of the module, so
556 we just store junk.  Then when we find the binding site, we fix it up.
557
558 \begin{code}
559 data NameSupply
560  = NameSupply { nsUniqs :: UniqSupply,
561                 -- Supply of uniques
562                 nsNames :: OrigNameCache,
563                 -- Ensures that one original name gets one unique
564                 nsIPs   :: OrigIParamCache
565                 -- Ensures that one implicit parameter name gets one unique
566    }
567
568 type OrigNameCache   = FiniteMap (ModuleName,OccName) Name
569 type OrigIParamCache = FiniteMap OccName Name
570 \end{code}
571
572 @ImportedModuleInfo@ contains info ONLY about modules that have not yet 
573 been loaded into the iPIT.  These modules are mentioned in interfaces we've
574 already read, so we know a tiny bit about them, but we havn't yet looked
575 at the interface file for the module itself.  It needs to persist across 
576 invocations of the renamer, at least from Rename.checkOldIface to Rename.renameSource.
577 And there's no harm in it persisting across multiple compilations.
578
579 \begin{code}
580 type ImportedModuleInfo = FiniteMap ModuleName (WhetherHasOrphans, IsBootInterface)
581 \end{code}
582
583 A DeclsMap contains a binding for each Name in the declaration
584 including the constructors of a type decl etc.  The Bool is True just
585 for the 'main' Name.
586
587 \begin{code}
588 type DeclsMap = (NameEnv (AvailInfo, Bool, (Module, RdrNameTyClDecl)), Int)
589                                                 -- The Int says how many have been sucked in
590
591 type IfaceInsts = GatedDecls RdrNameInstDecl
592 type IfaceRules = GatedDecls RdrNameRuleDecl
593
594 type GatedDecls d = (Bag (GatedDecl d), Int)    -- The Int says how many have been sucked in
595 type GatedDecl  d = ([Name], (Module, d))
596 \end{code}
597
598
599 %************************************************************************
600 %*                                                                      *
601 \subsection{Provenance and export info}
602 %*                                                                      *
603 %************************************************************************
604
605 A LocalRdrEnv is used for local bindings (let, where, lambda, case)
606
607 \begin{code}
608 type LocalRdrEnv = RdrNameEnv Name
609
610 extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv
611 extendLocalRdrEnv env names
612   = addListToRdrEnv env [(mkRdrUnqual (nameOccName n), n) | n <- names]
613 \end{code}
614
615 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
616 one for each module, corresponding to that module's top-level scope.
617
618 \begin{code}
619 type GlobalRdrEnv = RdrNameEnv [GlobalRdrElt]
620         -- The list is because there may be name clashes
621         -- These only get reported on lookup, not on construction
622
623 data GlobalRdrElt = GRE Name Provenance (Maybe DeprecTxt)
624         -- The Maybe DeprecTxt tells whether this name is deprecated
625
626 pprGlobalRdrEnv env
627   = vcat (map pp (rdrEnvToList env))
628   where
629     pp (rn, nps) = ppr rn <> colon <+> 
630                    vcat [ppr n <+> pprNameProvenance n p | (GRE n p _) <- nps]
631 \end{code}
632
633 The "provenance" of something says how it came to be in scope.
634
635 \begin{code}
636 data Provenance
637   = LocalDef                    -- Defined locally
638
639   | NonLocalDef                 -- Defined non-locally
640         ImportReason
641
642 -- Just used for grouping error messages (in RnEnv.warnUnusedBinds)
643 instance Eq Provenance where
644   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
645
646 instance Eq ImportReason where
647   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
648
649 instance Ord Provenance where
650    compare LocalDef LocalDef = EQ
651    compare LocalDef (NonLocalDef _) = LT
652    compare (NonLocalDef _) LocalDef = GT
653
654    compare (NonLocalDef reason1) (NonLocalDef reason2) 
655       = compare reason1 reason2
656
657 instance Ord ImportReason where
658    compare ImplicitImport ImplicitImport = EQ
659    compare ImplicitImport (UserImport _ _ _) = LT
660    compare (UserImport _ _ _) ImplicitImport = GT
661    compare (UserImport m1 loc1 _) (UserImport m2 loc2 _) 
662       = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
663
664
665 data ImportReason
666   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
667                                         -- Note the M may well not be the defining module
668                                         -- for this thing!
669         -- The Bool is true iff the thing was named *explicitly* in the import spec,
670         -- rather than being imported as part of a group; e.g.
671         --      import B
672         --      import C( T(..) )
673         -- Here, everything imported by B, and the constructors of T
674         -- are not named explicitly; only T is named explicitly.
675         -- This info is used when warning of unused names.
676
677   | ImplicitImport                      -- Imported implicitly for some other reason
678 \end{code}
679
680 \begin{code}
681 hasBetterProv :: Provenance -> Provenance -> Bool
682 -- Choose 
683 --      a local thing                 over an   imported thing
684 --      a user-imported thing         over a    non-user-imported thing
685 --      an explicitly-imported thing  over an   implicitly imported thing
686 hasBetterProv LocalDef                            _                            = True
687 hasBetterProv (NonLocalDef (UserImport _ _ _   )) (NonLocalDef ImplicitImport) = True
688 hasBetterProv _                                   _                            = False
689
690 pprNameProvenance :: Name -> Provenance -> SDoc
691 pprNameProvenance name LocalDef          = ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
692 pprNameProvenance name (NonLocalDef why) = sep [ppr_reason why, 
693                                                 nest 2 (parens (ppr_defn (nameSrcLoc name)))]
694
695 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
696 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
697
698 ppr_defn loc | isGoodSrcLoc loc = ptext SLIT("at") <+> ppr loc
699              | otherwise        = empty
700 \end{code}