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