[project @ 2003-02-12 15:01:31 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         HscEnv(..), 
9         GhciMode(..),
10
11         ModDetails(..), ModIface(..), 
12         ModGuts(..), ModImports(..), ForeignStubs(..),
13         ParsedIface(..), IfaceDeprecs,
14
15         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
16
17         ExternalPackageState(..), 
18         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
19         lookupIface, lookupIfaceByModName, moduleNameToModule,
20         emptyModIface,
21
22         InteractiveContext(..), emptyInteractiveContext, icPrintUnqual,
23
24         IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts,
25
26         VersionInfo(..), initialVersionInfo, lookupVersion,
27         FixityEnv, lookupFixity, collectFixities, emptyFixityEnv,
28
29         TyThing(..), implicitTyThings,
30
31         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
32         extendTypeEnvList, extendTypeEnvWithIds,
33         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
34
35         WhetherHasOrphans, IsBootInterface, DeclsMap, Usage(..), 
36         Dependencies(..), noDependencies,
37         IfaceInsts, IfaceRules, GatedDecl, GatedDecls, GateFn, 
38         NameCache(..), OrigNameCache, OrigIParamCache,
39         Avails, availsToNameSet, availName, availNames,
40         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
41         ExportItem, RdrExportItem,
42
43         PersistentCompilerState(..),
44
45         Deprecations(..), lookupDeprec, plusDeprecs,
46
47         InstEnv, ClsInstEnv, DFunId,
48         PackageInstEnv, PackageRuleBase,
49
50         GlobalRdrEnv, GlobalRdrElt(..), emptyGlobalRdrEnv, pprGlobalRdrEnv,
51         LocalRdrEnv, extendLocalRdrEnv, isLocalGRE, unQualInScope,
52         
53         -- Linker stuff
54         Linkable(..), isObjectLinkable,
55         Unlinked(..), CompiledByteCode,
56         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
57
58         -- Provenance
59         Provenance(..), ImportReason(..), 
60         pprNameProvenance, hasBetterProv
61
62     ) where
63
64 #include "HsVersions.h"
65
66 #ifdef GHCI
67 import ByteCodeAsm      ( CompiledByteCode )
68 #endif
69
70 import RdrName          ( RdrName, mkRdrUnqual, 
71                           RdrNameEnv, addListToRdrEnv, foldRdrEnv, isUnqual,
72                           rdrEnvToList, emptyRdrEnv )
73 import Name             ( Name, NamedThing, getName, nameOccName, nameModule, nameSrcLoc )
74 import NameEnv
75 import NameSet  
76 import OccName          ( OccName )
77 import Module
78 import InstEnv          ( InstEnv, ClsInstEnv, DFunId )
79 import Rules            ( RuleBase )
80 import CoreSyn          ( CoreBind )
81 import Id               ( Id, idName )
82 import Class            ( Class, classSelIds, classTyCon )
83 import TyCon            ( TyCon, tyConName, isNewTyCon, tyConGenIds, tyConSelIds, tyConDataCons )
84 import TcType           ( TyThing(..) )
85 import DataCon          ( dataConWorkId, dataConWrapId, dataConWrapId_maybe )
86 import Packages         ( PackageName, basePackage )
87 import CmdLineOpts      ( DynFlags )
88
89 import BasicTypes       ( Version, initialVersion, IPName,
90                           Fixity, FixitySig(..), defaultFixity )
91
92 import HsSyn            ( DeprecTxt, TyClDecl, InstDecl, RuleDecl,
93                           tyClDeclName, ifaceRuleDeclName, tyClDeclNames,
94                           instDeclDFun )
95 import RnHsSyn          ( RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl )
96
97 import CoreSyn          ( IdCoreRule )
98 import PrelNames        ( isBuiltInSyntaxName )
99
100 import FiniteMap
101 import Bag              ( Bag )
102 import Maybes           ( orElse )
103 import Outputable
104 import SrcLoc           ( SrcLoc, isGoodSrcLoc )
105 import Util             ( thenCmp, sortLt )
106 import UniqSupply       ( UniqSupply )
107 import Maybe            ( fromJust )
108 import FastString       ( FastString )
109
110 import Time             ( ClockTime )
111 \end{code}
112
113
114 %************************************************************************
115 %*                                                                      *
116 \subsection{Compilation environment}
117 %*                                                                      *
118 %************************************************************************
119
120 The HscEnv gives the environment in which to compile a chunk of code.
121
122 \begin{code}
123 data HscEnv = HscEnv { hsc_mode   :: GhciMode,
124                        hsc_dflags :: DynFlags,
125                        hsc_HPT    :: HomePackageTable }
126 \end{code}
127
128 The GhciMode is self-explanatory:
129
130 \begin{code}
131 data GhciMode = Batch | Interactive | OneShot 
132               deriving Eq
133 \end{code}
134
135 \begin{code}
136 type HomePackageTable  = ModuleEnv HomeModInfo  -- Domain = modules in the home package
137 type PackageIfaceTable = ModuleEnv ModIface     -- Domain = modules in the imported packages
138
139 emptyHomePackageTable  = emptyModuleEnv
140 emptyPackageIfaceTable = emptyModuleEnv
141
142 data HomeModInfo = HomeModInfo { hm_iface    :: ModIface,
143                                  hm_details  :: ModDetails,
144                                  hm_linkable :: Linkable }
145 \end{code}
146
147 Simple lookups in the symbol table.
148
149 \begin{code}
150 lookupIface :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
151 -- We often have two IfaceTables, and want to do a lookup
152 lookupIface hpt pit mod
153   = case lookupModuleEnv hpt mod of
154         Just mod_info -> Just (hm_iface mod_info)
155         Nothing       -> lookupModuleEnv pit mod
156
157 lookupIfaceByModName :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
158 -- We often have two IfaceTables, and want to do a lookup
159 lookupIfaceByModName hpt pit mod
160   = case lookupModuleEnvByName hpt mod of
161         Just mod_info -> Just (hm_iface mod_info)
162         Nothing       -> lookupModuleEnvByName pit mod
163 \end{code}
164
165 \begin{code}
166 -- Use instead of Finder.findModule if possible: this way doesn't
167 -- require filesystem operations, and it is guaranteed not to fail
168 -- when the IfaceTables are properly populated (i.e. after the renamer).
169 moduleNameToModule :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Module
170 moduleNameToModule hpt pit mod 
171    = mi_module (fromJust (lookupIfaceByModName hpt pit mod))
172 \end{code}
173
174
175 %************************************************************************
176 %*                                                                      *
177 \subsection{Symbol tables and Module details}
178 %*                                                                      *
179 %************************************************************************
180
181 A @ModIface@ plus a @ModDetails@ summarises everything we know 
182 about a compiled module.  The @ModIface@ is the stuff *before* linking,
183 and can be written out to an interface file.  (The @ModDetails@ is after 
184 linking; it is the "linked" form of the mi_decls field.)
185
186 When we *read* an interface file, we also construct a @ModIface@ from it,
187 except that the mi_decls part is empty; when reading we consolidate
188 the declarations into a single indexed map in the @PersistentRenamerState@.
189
190 \begin{code}
191 data ModIface 
192    = ModIface {
193         mi_module   :: !Module,
194         mi_package  :: !PackageName,        -- Which package the module comes from
195         mi_version  :: !VersionInfo,        -- Version info for everything in this module
196         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
197         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
198
199         mi_deps     :: Dependencies,
200                 -- This is consulted for directly-imported modules, but
201                 -- not for anything else
202
203         mi_usages   :: [Usage Name],
204                 -- Usages; kept sorted so that it's easy to decide
205                 -- whether to write a new iface file (changing usages
206                 -- doesn't affect the version of this module)
207                 -- NOT STRICT!  we read this field lazily from the interface file
208                 -- It is *only* consulted by the recompilation checker
209
210         mi_exports  :: ![ExportItem],
211                 -- What it exports Kept sorted by (mod,occ), to make
212                 -- version comparisons easier
213
214         mi_globals  :: !(Maybe GlobalRdrEnv),
215                 -- Its top level environment or Nothing if we read this
216                 -- interface from an interface file.  (We need the source
217                 -- file to figure out the top-level environment.)
218
219         mi_fixities :: !FixityEnv,          -- Fixities
220         mi_deprecs  :: Deprecations,        -- Deprecations
221                 -- NOT STRICT!  we read this field lazilly from the interface file
222
223         mi_decls    :: IfaceDecls           -- The RnDecls form of ModDetails
224                 -- NOT STRICT!  we fill this field with _|_ sometimes
225      }
226
227 -- Should be able to construct ModDetails from mi_decls in ModIface
228 data ModDetails
229    = ModDetails {
230         -- The next three fields are created by the typechecker
231         md_types    :: !TypeEnv,
232         md_insts    :: ![DFunId],       -- Dfun-ids for the instances in this module
233         md_rules    :: ![IdCoreRule]    -- Domain may include Ids from other modules
234      }
235
236 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
237 -- There is only one ModGuts at any time, the one for the module
238 -- being compiled right now.  Once it is compiled, a ModIface and 
239 -- ModDetails are extracted and the ModGuts is dicarded.
240
241 data ModGuts
242   = ModGuts {
243         mg_module   :: !Module,
244         mg_exports  :: !Avails,         -- What it exports
245         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
246         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
247                                         --      generate initialisation code
248         mg_usages   :: ![Usage Name],   -- Version info for what it needed
249
250         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
251         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
252         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
253
254         mg_types    :: !TypeEnv,
255         mg_insts    :: ![DFunId],       -- Instances 
256         mg_rules    :: ![IdCoreRule],   -- Rules from this module
257         mg_binds    :: ![CoreBind],     -- Bindings for this module
258         mg_foreign  :: !ForeignStubs
259     }
260
261 -- The ModGuts takes on several slightly different forms:
262 --
263 -- After simplification, the following fields change slightly:
264 --      mg_rules        Orphan rules only (local ones now attached to binds)
265 --      mg_binds        With rules attached
266 --
267 -- After CoreTidy, the following fields change slightly:
268 --      mg_types        Now contains Ids as well, replete with final IdInfo
269 --                         The Ids are only the ones that are visible from
270 --                         importing modules.  Without -O that means only
271 --                         exported Ids, but with -O importing modules may
272 --                         see ids mentioned in unfoldings of exported Ids
273 --
274 --      mg_insts        Same DFunIds as before, but with final IdInfo,
275 --                         and the unique might have changed; remember that
276 --                         CoreTidy links up the uniques of old and new versions
277 --
278 --      mg_rules        All rules for exported things, substituted with final Ids
279 --
280 --      mg_binds        Tidied
281
282
283
284 data ModImports
285   = ModImports {
286         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
287                                                 -- Boolean is true if we imported the whole
288                                                 --      module (apart, perhaps, from hiding some)
289         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
290                                                 --      directly or indirectly
291         imp_home_names :: !NameSet              -- Home package things on which we depend,
292                                                 --      directly or indirectly
293     }
294
295 data ForeignStubs = NoStubs
296                   | ForeignStubs
297                         SDoc            -- Header file prototypes for
298                                         --      "foreign exported" functions
299                         SDoc            -- C stubs to use when calling
300                                         --      "foreign exported" functions
301                         [FastString]    -- Headers that need to be included
302                                         --      into C code generated for this module
303                         [Id]            -- Foreign-exported binders
304                                         --      we have to generate code to register these
305
306
307 data IfaceDecls = IfaceDecls { dcl_tycl  :: [RenamedTyClDecl],  -- Sorted
308                                dcl_rules :: [RenamedRuleDecl],  -- Sorted
309                                dcl_insts :: [RenamedInstDecl] } -- Unsorted
310
311 mkIfaceDecls :: [RenamedTyClDecl] -> [RenamedRuleDecl] -> [RenamedInstDecl] -> IfaceDecls
312 -- Sort to put them in canonical order for version comparison
313 mkIfaceDecls tycls rules insts
314   = IfaceDecls { dcl_tycl  = sortLt lt_tycl tycls,
315                  dcl_rules = sortLt lt_rule rules,
316                  dcl_insts = sortLt lt_inst insts }
317   where
318     d1 `lt_tycl` d2 = tyClDeclName      d1 < tyClDeclName      d2
319     r1 `lt_rule` r2 = ifaceRuleDeclName r1 < ifaceRuleDeclName r2
320     i1 `lt_inst` i2 = instDeclDFun      i1 < instDeclDFun      i2
321 \end{code}
322
323 \begin{code}
324 emptyModIface :: Module -> ModIface
325 emptyModIface mod
326   = ModIface { mi_module   = mod,
327                mi_package  = basePackage, -- XXX fully bogus
328                mi_version  = initialVersionInfo,
329                mi_usages   = [],
330                mi_deps     = noDependencies,
331                mi_orphan   = False,
332                mi_boot     = False,
333                mi_exports  = [],
334                mi_fixities = emptyNameEnv,
335                mi_globals  = Nothing,
336                mi_deprecs  = NoDeprecs,
337                mi_decls    = panic "emptyModIface: decls"
338     }           
339 \end{code}
340
341
342 %************************************************************************
343 %*                                                                      *
344                 Parsed interface files
345 %*                                                                      *
346 %************************************************************************
347
348 A ParsedIface is exactly as read from an interface file.
349
350 \begin{code}
351 type IfaceDeprecs = Maybe (Either DeprecTxt [(RdrName,DeprecTxt)])
352         -- Nothing        => NoDeprecs
353         -- Just (Left t)  => DeprecAll
354         -- Just (Right p) => DeprecSome
355
356 data ParsedIface
357   = ParsedIface {
358       pi_mod       :: ModuleName,
359       pi_pkg       :: PackageName,
360       pi_vers      :: Version,                          -- Module version number
361       pi_orphan    :: WhetherHasOrphans,                -- Whether this module has orphans
362       pi_deps      :: Dependencies,                     -- What it depends on
363       pi_usages    :: [Usage OccName],                  -- Usages
364       pi_exports   :: (Version, [RdrExportItem]),       -- Exports
365       pi_decls     :: [(Version, TyClDecl RdrName)],    -- Local definitions
366       pi_fixity    :: [FixitySig RdrName],              -- Local fixity declarations,
367       pi_insts     :: [InstDecl RdrName],               -- Local instance declarations
368       pi_rules     :: (Version, [RuleDecl RdrName]),    -- Rules, with their version
369       pi_deprecs   :: IfaceDeprecs                      -- Deprecations
370     }
371 \end{code}
372
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection{The interactive context}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381 data InteractiveContext 
382   = InteractiveContext { 
383         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
384                                         -- these modules
385
386         ic_exports :: [Module],         -- Include just the exports of these
387                                         -- modules
388
389         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
390                                         -- ic_toplev_scope and ic_exports
391
392         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
393                                         -- during interaction
394
395         ic_type_env :: TypeEnv          -- Ditto for types
396     }
397
398 emptyInteractiveContext
399   = InteractiveContext { ic_toplev_scope = [],
400                          ic_exports = [],
401                          ic_rn_gbl_env = emptyRdrEnv,
402                          ic_rn_local_env = emptyRdrEnv,
403                          ic_type_env = emptyTypeEnv }
404
405 icPrintUnqual :: InteractiveContext -> PrintUnqualified
406 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
407 \end{code}
408
409
410 %************************************************************************
411 %*                                                                      *
412 \subsection{Type environment stuff}
413 %*                                                                      *
414 %************************************************************************
415
416 \begin{code}
417 typeEnvElts    :: TypeEnv -> [TyThing]
418 typeEnvClasses :: TypeEnv -> [Class]
419 typeEnvTyCons  :: TypeEnv -> [TyCon]
420 typeEnvIds     :: TypeEnv -> [Id]
421
422 typeEnvElts    env = nameEnvElts env
423 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
424 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
425 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
426 \end{code}
427
428
429 \begin{code}
430 type TypeEnv = NameEnv TyThing
431
432 emptyTypeEnv = emptyNameEnv
433
434 mkTypeEnv :: [TyThing] -> TypeEnv
435 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
436                 
437 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
438 -- Extend the type environment
439 extendTypeEnvList env things
440   = foldl extend env things
441   where
442     extend env thing = extendNameEnv env (getName thing) thing
443
444 implicitTyThings :: [TyThing] -> [TyThing]
445 implicitTyThings things
446   = concatMap extras things
447   where
448     extras_plus thing = thing : extras thing
449
450     extras (AnId id)   = []
451
452         -- For type constructors, add the data cons (and their extras),
453         -- and the selectors and generic-programming Ids too
454         --
455         -- Newtypes don't have a worker Id, so don't generate that
456     extras (ATyCon tc) = map AnId (tyConGenIds tc ++ tyConSelIds tc) ++ data_con_stuff
457        where
458         data_con_stuff | isNewTyCon tc = [ADataCon dc1, AnId (dataConWrapId dc1)]
459                        | otherwise     = concatMap (extras_plus . ADataCon) dcs
460         dcs = tyConDataCons tc
461         dc1 = head dcs
462                      
463         -- For classes, add the class TyCon too (and its extras)
464         -- and the class selector Ids
465     extras (AClass cl) = map AnId (classSelIds cl) ++
466                          extras_plus (ATyCon (classTyCon cl))
467                          
468
469         -- For data cons add the worker and wrapper (if any)
470     extras (ADataCon dc) 
471         = AnId (dataConWorkId dc) : wrap_id_stuff
472         where
473                 -- May or may not have a wrapper
474           wrap_id_stuff = case dataConWrapId_maybe dc of 
475                                 Just id -> [AnId id]
476                                 Nothing -> []
477
478 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
479 extendTypeEnvWithIds env ids
480   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
481 \end{code}
482
483 \begin{code}
484 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
485 lookupType hpt pte name
486   = case lookupModuleEnv hpt (nameModule name) of
487         Just details -> lookupNameEnv (md_types (hm_details details)) name
488         Nothing      -> lookupNameEnv pte name
489 \end{code}
490
491 %************************************************************************
492 %*                                                                      *
493 \subsection{Auxiliary types}
494 %*                                                                      *
495 %************************************************************************
496
497 These types are defined here because they are mentioned in ModDetails,
498 but they are mostly elaborated elsewhere
499
500 \begin{code}
501 data VersionInfo 
502   = VersionInfo {
503         vers_module  :: Version,        -- Changes when anything changes
504         vers_exports :: Version,        -- Changes when export list changes
505         vers_rules   :: Version,        -- Changes when any rule changes
506         vers_decls   :: NameEnv Version
507                 -- Versions for "big" names only (not data constructors, class ops)
508                 -- The version of an Id changes if its fixity changes
509                 -- Ditto data constructors, class operations, except that the version of
510                 -- the parent class/tycon changes
511                 --
512                 -- If a name isn't in the map, it means 'initialVersion'
513     }
514
515 initialVersionInfo :: VersionInfo
516 initialVersionInfo = VersionInfo { vers_module  = initialVersion,
517                                    vers_exports = initialVersion,
518                                    vers_rules   = initialVersion,
519                                    vers_decls   = emptyNameEnv
520                         }
521
522 lookupVersion :: NameEnv Version -> Name -> Version
523 lookupVersion env name = lookupNameEnv env name `orElse` initialVersion
524
525 data Deprecations = NoDeprecs
526                   | DeprecAll DeprecTxt                         -- Whole module deprecated
527                   | DeprecSome (NameEnv (Name,DeprecTxt))       -- Some things deprecated
528                                                                 -- Just "big" names
529                 -- We keep the Name in the range, so we can print them out
530
531 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
532 lookupDeprec NoDeprecs        name = Nothing
533 lookupDeprec (DeprecAll  txt) name = Just txt
534 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
535                                             Just (_, txt) -> Just txt
536                                             Nothing       -> Nothing
537
538 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
539 plusDeprecs d NoDeprecs = d
540 plusDeprecs NoDeprecs d = d
541 plusDeprecs d (DeprecAll t) = DeprecAll t
542 plusDeprecs (DeprecAll t) d = DeprecAll t
543 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
544
545 instance Eq Deprecations where
546   -- Used when checking whether we need write a new interface
547   NoDeprecs       == NoDeprecs       = True
548   (DeprecAll t1)  == (DeprecAll t2)  = t1 == t2
549   (DeprecSome e1) == (DeprecSome e2) = nameEnvElts e1 == nameEnvElts e2
550   d1              == d2              = False
551 \end{code}
552
553
554 \begin{code}
555 type Avails       = [AvailInfo]
556 type AvailInfo    = GenAvailInfo Name
557 type RdrAvailInfo = GenAvailInfo OccName
558
559 data GenAvailInfo name  = Avail name     -- An ordinary identifier
560                         | AvailTC name   -- The name of the type or class
561                                   [name] -- The available pieces of type/class.
562                                          -- NB: If the type or class is itself
563                                          -- to be in scope, it must be in this list.
564                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
565                         deriving( Eq )
566                         -- Equality used when deciding if the interface has changed
567
568 type RdrExportItem = (ModuleName, [RdrAvailInfo])
569 type ExportItem    = (ModuleName, [AvailInfo])
570
571 availsToNameSet :: [AvailInfo] -> NameSet
572 availsToNameSet avails = foldl add emptyNameSet avails
573                        where
574                          add set avail = addListToNameSet set (availNames avail)
575
576 availName :: GenAvailInfo name -> name
577 availName (Avail n)     = n
578 availName (AvailTC n _) = n
579
580 availNames :: GenAvailInfo name -> [name]
581 availNames (Avail n)      = [n]
582 availNames (AvailTC n ns) = ns
583
584 instance Outputable n => Outputable (GenAvailInfo n) where
585    ppr = pprAvail
586
587 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
588 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
589                                         []  -> empty
590                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
591
592 pprAvail (Avail n) = ppr n
593 \end{code}
594
595 \begin{code}
596 type FixityEnv = NameEnv (FixitySig Name)
597         -- We keep the whole fixity sig so that we
598         -- can report line-number info when there is a duplicate
599         -- fixity declaration
600
601 emptyFixityEnv :: FixityEnv
602 emptyFixityEnv = emptyNameEnv
603
604 lookupFixity :: FixityEnv -> Name -> Fixity
605 lookupFixity env n = case lookupNameEnv env n of
606                         Just (FixitySig _ fix _) -> fix
607                         Nothing                  -> defaultFixity
608
609 collectFixities :: FixityEnv -> [TyClDecl Name] -> [FixitySig Name]
610 -- Collect fixities for the specified declarations
611 collectFixities env decls
612   = [ fix
613     | d <- decls, (n,_) <- tyClDeclNames d,
614       Just fix <- [lookupNameEnv env n]
615     ]
616 \end{code}
617
618
619 %************************************************************************
620 %*                                                                      *
621 \subsection{WhatsImported}
622 %*                                                                      *
623 %************************************************************************
624
625 \begin{code}
626 type WhetherHasOrphans   = Bool
627         -- An "orphan" is 
628         --      * an instance decl in a module other than the defn module for 
629         --              one of the tycons or classes in the instance head
630         --      * a transformation rule in a module other than the one defining
631         --              the function in the head of the rule.
632
633 type IsBootInterface = Bool
634
635 -- Dependency info about modules and packages below this one
636 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
637 --
638 -- Invariant: the dependencies of a module M never includes M
639 data Dependencies
640   = Deps { dep_mods  :: [(ModuleName,IsBootInterface)], -- Home-package module dependencies
641            dep_pkgs  :: [PackageName],                  -- External package dependencies
642            dep_orphs :: [ModuleName] }                  -- Orphan modules (whether home or external pkg)
643
644 noDependencies :: Dependencies
645 noDependencies = Deps [] [] []
646           
647 data Usage name 
648   = Usage { usg_name     :: ModuleName,         -- Name of the module
649             usg_mod      :: Version,            -- Module version
650             usg_exports  :: Maybe Version,      -- Export-list version, if we depend on it
651             usg_entities :: [(name,Version)],   -- Sorted by occurrence name
652             usg_rules    :: Version             -- Rules version
653     }       deriving( Eq )
654         -- This type doesn't let you say "I imported f but none of the rules in
655         -- the module". If you use anything in the module you get its rule version
656         -- So if the rules change, you'll recompile, even if you don't use them.
657         -- This is easy to implement, and it's safer: you might not have used the rules last
658         -- time round, but if someone has added a new rule you might need it this time
659
660         -- The export list field is (Just v) if we depend on the export list:
661         --      i.e. we imported the module without saying exactly what we imported
662         -- We need to recompile if the module exports changes, because we might
663         -- now have a name clash in the importing module.
664 \end{code}
665
666
667 %************************************************************************
668 %*                                                                      *
669 \subsection{The persistent compiler state}
670 %*                                                                      *
671 %************************************************************************
672
673 The @PersistentCompilerState@ persists across successive calls to the
674 compiler.
675
676 \begin{code}
677 data PersistentCompilerState 
678    = PCS {
679         pcs_nc  :: !NameCache,
680         pcs_EPS :: !ExternalPackageState
681      }
682 \end{code}
683
684
685 \begin{code}
686 type PackageTypeEnv  = TypeEnv
687 type PackageRuleBase = RuleBase
688 type PackageInstEnv  = InstEnv
689
690 data ExternalPackageState
691   = EPS {
692         eps_PIT :: !PackageIfaceTable,
693                 -- The ModuleIFaces for modules in external packages
694                 -- whose interfaces we have opened
695                 -- The declarations in these interface files are held in
696                 -- eps_decls, eps_insts, eps_rules (below), not in the 
697                 -- mi_decls fields of the iPIT.  
698                 -- What _is_ in the iPIT is:
699                 --      * The Module 
700                 --      * Version info
701                 --      * Its exports
702                 --      * Fixities
703                 --      * Deprecations
704
705         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
706
707         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
708                                                 --   all the external-package modules
709         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
710
711
712         -- Holding pens for stuff that has been read in from file,
713         -- but not yet slurped into the renamer
714         eps_decls      :: !DeclsMap,
715                 -- A single, global map of Names to unslurped decls
716         eps_insts      :: !IfaceInsts,
717                 -- The as-yet un-slurped instance decls; this bag is depleted when we
718                 -- slurp an instance decl so that we don't slurp the same one twice.
719                 -- Each is 'gated' by the names that must be available before
720                 -- this instance decl is needed.
721         eps_rules      :: !IfaceRules,
722                 -- Similar to instance decls, only for rules
723
724         eps_inst_gates :: !NameSet      -- Gates for instance decls
725                 -- The instance gates must accumulate across
726                 -- all invocations of the renamer; 
727                 -- see "the gating story" in RnIfaces.lhs
728                 -- These names should all be from other packages;
729                 -- for the home package we have all the instance
730                 -- declarations anyhow
731   }
732 \end{code}
733
734 The NameCache makes sure that there is just one Unique assigned for
735 each original name; i.e. (module-name, occ-name) pair.  The Name is
736 always stored as a Global, and has the SrcLoc of its binding location.
737 Actually that's not quite right.  When we first encounter the original
738 name, we might not be at its binding site (e.g. we are reading an
739 interface file); so we give it 'noSrcLoc' then.  Later, when we find
740 its binding site, we fix it up.
741
742 Exactly the same is true of the Module stored in the Name.  When we first
743 encounter the occurrence, we may not know the details of the module, so
744 we just store junk.  Then when we find the binding site, we fix it up.
745
746 \begin{code}
747 data NameCache
748  = NameCache {  nsUniqs :: UniqSupply,
749                 -- Supply of uniques
750                 nsNames :: OrigNameCache,
751                 -- Ensures that one original name gets one unique
752                 nsIPs   :: OrigIParamCache
753                 -- Ensures that one implicit parameter name gets one unique
754    }
755
756 type OrigNameCache = ModuleEnv (Module, OccNameCache)
757         -- Maps a module *name* to a Module, 
758         -- plus the OccNameEnv fot that module
759 type OccNameCache = FiniteMap OccName Name
760         -- Maps the OccName to a Name
761         -- A FiniteMap because OccNames have a Namespace/Faststring pair
762
763 type OrigIParamCache = FiniteMap (IPName RdrName) (IPName Name)
764 \end{code}
765
766 A DeclsMap contains a binding for each Name in the declaration
767 including the constructors of a type decl etc.  The Bool is True just
768 for the 'main' Name.
769
770 \begin{code}
771 type DeclsMap = (NameEnv (AvailInfo, Bool, (Module, TyClDecl RdrName)), Int)
772                                                 -- The Int says how many have been sucked in
773
774 type IfaceInsts = GatedDecls (InstDecl RdrName)
775 type IfaceRules = GatedDecls (RuleDecl RdrName)
776
777 type GatedDecls d = (Bag (GatedDecl d), Int)    -- The Int says how many have been sucked in
778 type GatedDecl  d = (GateFn, (Module, d))
779 type GateFn       = (Name -> Bool) -> Bool      -- Returns True <=> gate is open
780                                                 -- The (Name -> Bool) fn returns True for visible Names
781         -- For example, suppose this is in an interface file
782         --      instance C T where ...
783         -- We want to slurp this decl if both C and T are "visible" in 
784         -- the importing module.  See "The gating story" in RnIfaces for details.
785 \end{code}
786
787
788 %************************************************************************
789 %*                                                                      *
790 \subsection{Linkable stuff}
791 %*                                                                      *
792 %************************************************************************
793
794 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
795 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
796
797 \begin{code}
798 data Linkable = LM {
799   linkableTime     :: ClockTime,        -- Time at which this linkable was built
800                                         -- (i.e. when the bytecodes were produced,
801                                         --       or the mod date on the files)
802   linkableModName  :: ModuleName,       -- Should be Module, but see below
803   linkableUnlinked :: [Unlinked]
804  }
805
806 isObjectLinkable :: Linkable -> Bool
807 isObjectLinkable l = all isObject (linkableUnlinked l)
808
809 instance Outputable Linkable where
810    ppr (LM when_made mod unlinkeds)
811       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
812         $$ nest 3 (ppr unlinkeds)
813
814 -------------------------------------------
815 data Unlinked
816    = DotO FilePath
817    | DotA FilePath
818    | DotDLL FilePath
819    | BCOs CompiledByteCode
820
821 #ifndef GHCI
822 data CompiledByteCode = NoByteCode
823 #endif
824
825 instance Outputable Unlinked where
826    ppr (DotO path)   = text "DotO" <+> text path
827    ppr (DotA path)   = text "DotA" <+> text path
828    ppr (DotDLL path) = text "DotDLL" <+> text path
829 #ifdef GHCI
830    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
831 #else
832    ppr (BCOs bcos)   = text "No byte code"
833 #endif
834
835 isObject (DotO _)   = True
836 isObject (DotA _)   = True
837 isObject (DotDLL _) = True
838 isObject _          = False
839
840 isInterpretable = not . isObject
841
842 nameOfObject (DotO fn)   = fn
843 nameOfObject (DotA fn)   = fn
844 nameOfObject (DotDLL fn) = fn
845
846 byteCodeOfObject (BCOs bc) = bc
847 \end{code}
848
849
850 %************************************************************************
851 %*                                                                      *
852 \subsection{Provenance and export info}
853 %*                                                                      *
854 %************************************************************************
855
856 A LocalRdrEnv is used for local bindings (let, where, lambda, case)
857 Also used in 
858
859 \begin{code}
860 type LocalRdrEnv = RdrNameEnv Name
861
862 extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv
863 extendLocalRdrEnv env names
864   = addListToRdrEnv env [(mkRdrUnqual (nameOccName n), n) | n <- names]
865 \end{code}
866
867 The GlobalRdrEnv gives maps RdrNames to Names.  There is a separate
868 one for each module, corresponding to that module's top-level scope.
869
870 \begin{code}
871 type GlobalRdrEnv = RdrNameEnv [GlobalRdrElt]
872         -- The list is because there may be name clashes
873         -- These only get reported on lookup, not on construction
874
875 emptyGlobalRdrEnv = emptyRdrEnv
876
877 data GlobalRdrElt 
878   = GRE { gre_name   :: Name,
879           gre_parent :: Maybe Name,     -- Name of the "parent" structure, for
880                                         --      * the tycon of a data con
881                                         --      * the class of a class op
882                                         -- For others it's Nothing
883                 -- Invariant: gre_name g /= gre_parent g
884                 --      when the latter is a Just
885
886           gre_prov   :: Provenance,     -- Why it's in scope
887           gre_deprec :: Maybe DeprecTxt -- Whether this name is deprecated
888     }
889
890 instance Outputable GlobalRdrElt where
891   ppr gre = ppr (gre_name gre) <+> 
892             parens (pp_parent (gre_parent gre) <+> pprNameProvenance gre)
893           where
894             pp_parent (Just p) = text "parent:" <+> ppr p <> comma
895             pp_parent Nothing  = empty
896
897 pprGlobalRdrEnv env
898   = vcat (map pp (rdrEnvToList env))
899   where
900     pp (rn, gres) = ppr rn <> colon <+> 
901                     vcat [ ppr (gre_name gre) <+> pprNameProvenance gre
902                          | gre <- gres]
903
904 isLocalGRE :: GlobalRdrElt -> Bool
905 isLocalGRE (GRE {gre_prov = LocalDef}) = True
906 isLocalGRE other                       = False
907 \end{code}
908
909 @unQualInScope@ returns a function that takes a @Name@ and tells whether
910 its unqualified name is in scope.  This is put as a boolean flag in
911 the @Name@'s provenance to guide whether or not to print the name qualified
912 in error messages.
913
914 \begin{code}
915 unQualInScope :: GlobalRdrEnv -> Name -> Bool
916 -- True if 'f' is in scope, and has only one binding,
917 -- and the thing it is bound to is the name we are looking for
918 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
919 --
920 -- Also checks for built-in syntax, which is always 'in scope'
921 --
922 -- This fn is only efficient if the shared 
923 -- partial application is used a lot.
924 unQualInScope env
925   = \n -> n `elemNameSet` unqual_names || isBuiltInSyntaxName n
926   where
927     unqual_names :: NameSet
928     unqual_names = foldRdrEnv add emptyNameSet env
929     add rdr_name [gre] unquals | isUnqual rdr_name = addOneToNameSet unquals (gre_name gre)
930     add _        _     unquals                     = unquals
931 \end{code}
932
933 The "provenance" of something says how it came to be in scope.
934
935 \begin{code}
936 data Provenance
937   = LocalDef                    -- Defined locally
938
939   | NonLocalDef                 -- Defined non-locally
940         ImportReason
941
942 -- Just used for grouping error messages (in RnEnv.warnUnusedBinds)
943 instance Eq Provenance where
944   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
945
946 instance Eq ImportReason where
947   p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False
948
949 instance Ord Provenance where
950    compare LocalDef LocalDef = EQ
951    compare LocalDef (NonLocalDef _) = LT
952    compare (NonLocalDef _) LocalDef = GT
953
954    compare (NonLocalDef reason1) (NonLocalDef reason2) 
955       = compare reason1 reason2
956
957 instance Ord ImportReason where
958    compare ImplicitImport ImplicitImport = EQ
959    compare ImplicitImport (UserImport _ _ _) = LT
960    compare (UserImport _ _ _) ImplicitImport = GT
961    compare (UserImport m1 loc1 _) (UserImport m2 loc2 _) 
962       = (m1 `compare` m2) `thenCmp` (loc1 `compare` loc2)
963
964
965 data ImportReason
966   = UserImport Module SrcLoc Bool       -- Imported from module M on line L
967                                         -- Note the M may well not be the defining module
968                                         -- for this thing!
969         -- The Bool is true iff the thing was named *explicitly* in the import spec,
970         -- rather than being imported as part of a group; e.g.
971         --      import B
972         --      import C( T(..) )
973         -- Here, everything imported by B, and the constructors of T
974         -- are not named explicitly; only T is named explicitly.
975         -- This info is used when warning of unused names.
976
977   | ImplicitImport                      -- Imported implicitly for some other reason
978 \end{code}
979
980 \begin{code}
981 hasBetterProv :: Provenance -> Provenance -> Bool
982 -- Choose 
983 --      a local thing                 over an   imported thing
984 --      a user-imported thing         over a    non-user-imported thing
985 --      an explicitly-imported thing  over an   implicitly imported thing
986 hasBetterProv LocalDef                            _                            = True
987 hasBetterProv (NonLocalDef (UserImport _ _ _   )) (NonLocalDef ImplicitImport) = True
988 hasBetterProv _                                   _                            = False
989
990 pprNameProvenance :: GlobalRdrElt -> SDoc
991 pprNameProvenance (GRE {gre_name = name, gre_prov = prov})
992   = case prov of
993         LocalDef        -> ptext SLIT("defined at") <+> ppr (nameSrcLoc name)
994         NonLocalDef why ->  sep [ppr_reason why, 
995                                  nest 2 (ppr_defn (nameSrcLoc name))]
996
997 ppr_reason ImplicitImport         = ptext SLIT("implicitly imported")
998 ppr_reason (UserImport mod loc _) = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc
999
1000 ppr_defn loc | isGoodSrcLoc loc = parens (ptext SLIT("defined at") <+> ppr loc)
1001              | otherwise        = empty
1002 \end{code}