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