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