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