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