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