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