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