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