[project @ 2005-05-17 08:48:28 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         -- * Sessions and compilation state
9         Session(..), HscEnv(..), hscEPS,
10         FinderCache, FinderCacheEntry,
11         Target(..), TargetId(..), pprTarget, pprTargetId,
12         ModuleGraph, emptyMG,
13
14         ModDetails(..), emptyModDetails,
15         ModGuts(..), CgGuts(..), ModImports(..), ForeignStubs(..),
16
17         ModSummary(..), showModMsg, isBootSummary,
18         msHsFilePath, msHiFilePath, msObjFilePath, 
19
20         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
21         
22         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
23         hptInstances, hptRules,
24
25         ExternalPackageState(..), EpsStats(..), addEpsInStats,
26         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
27         lookupIface, lookupIfaceByModule, emptyModIface,
28
29         InteractiveContext(..), emptyInteractiveContext, 
30         icPrintUnqual, unQualInScope,
31
32         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
33         emptyIfaceDepCache, 
34
35         Deprecs(..), IfaceDeprecs,
36
37         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
38
39         implicitTyThings, 
40
41         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
42         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
43         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
44         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
45
46         WhetherHasOrphans, IsBootInterface, Usage(..), 
47         Dependencies(..), noDependencies,
48         NameCache(..), OrigNameCache, OrigIParamCache,
49         Avails, availsToNameSet, availName, availNames,
50         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
51         IfaceExport,
52
53         Deprecations, DeprecTxt, lookupDeprec, plusDeprecs,
54
55         PackageInstEnv, PackageRuleBase,
56
57         -- Linker stuff
58         Linkable(..), isObjectLinkable,
59         Unlinked(..), CompiledByteCode,
60         isObject, nameOfObject, isInterpretable, byteCodeOfObject
61     ) where
62
63 #include "HsVersions.h"
64
65 #ifdef GHCI
66 import ByteCodeAsm      ( CompiledByteCode )
67 #endif
68
69 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv,
70                           LocalRdrEnv, emptyLocalRdrEnv,
71                           GlobalRdrElt(..), mkRdrUnqual, lookupGRE_RdrName )
72 import Name             ( Name, NamedThing, getName, nameOccName, nameModule )
73 import NameEnv
74 import NameSet  
75 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
76                           extendOccEnv )
77 import Module
78 import InstEnv          ( InstEnv, Instance )
79 import Rules            ( RuleBase )
80 import CoreSyn          ( CoreBind )
81 import Id               ( Id )
82 import Type             ( TyThing(..) )
83
84 import Class            ( Class, classSelIds, classTyCon )
85 import TyCon            ( TyCon, tyConSelIds, tyConDataCons )
86 import DataCon          ( dataConImplicitIds )
87 import Packages         ( PackageIdH, PackageId, PackageConfig )
88 import DynFlags         ( DynFlags(..), isOneShot )
89 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
90 import BasicTypes       ( Version, initialVersion, IPName, 
91                           Fixity, defaultFixity, DeprecTxt )
92
93 import IfaceSyn         ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
94
95 import FiniteMap        ( FiniteMap )
96 import CoreSyn          ( CoreRule )
97 import Maybes           ( orElse, fromJust, expectJust )
98 import Outputable
99 import SrcLoc           ( SrcSpan )
100 import UniqSupply       ( UniqSupply )
101 import FastString       ( FastString )
102
103 import DATA_IOREF       ( IORef, readIORef )
104 import StringBuffer     ( StringBuffer )
105 import Time             ( ClockTime )
106 \end{code}
107
108
109 %************************************************************************
110 %*                                                                      *
111 \subsection{Compilation environment}
112 %*                                                                      *
113 %************************************************************************
114
115
116 \begin{code}
117 -- | The Session is a handle to the complete state of a compilation
118 -- session.  A compilation session consists of a set of modules
119 -- constituting the current program or library, the context for
120 -- interactive evaluation, and various caches.
121 newtype Session = Session (IORef HscEnv)
122 \end{code}
123
124 HscEnv is like Session, except that some of the fields are immutable.
125 An HscEnv is used to compile a single module from plain Haskell source
126 code (after preprocessing) to either C, assembly or C--.  Things like
127 the module graph don't change during a single compilation.
128
129 Historical note: "hsc" used to be the name of the compiler binary,
130 when there was a separate driver and compiler.  To compile a single
131 module, the driver would invoke hsc on the source code... so nowadays
132 we think of hsc as the layer of the compiler that deals with compiling
133 a single module.
134
135 \begin{code}
136 data HscEnv 
137   = HscEnv { 
138         hsc_dflags :: DynFlags,
139                 -- The dynamic flag settings
140
141         hsc_targets :: [Target],
142                 -- The targets (or roots) of the current session
143
144         hsc_mod_graph :: ModuleGraph,
145                 -- The module graph of the current session
146
147         hsc_IC :: InteractiveContext,
148                 -- The context for evaluating interactive statements
149
150         hsc_HPT    :: HomePackageTable,
151                 -- The home package table describes already-compiled
152                 -- home-packge modules, *excluding* the module we 
153                 -- are compiling right now.
154                 -- (In one-shot mode the current module is the only
155                 --  home-package module, so hsc_HPT is empty.  All other
156                 --  modules count as "external-package" modules.
157                 --  However, even in GHCi mode, hi-boot interfaces are
158                 --  demand-loadeded into the external-package table.)
159                 --
160                 -- hsc_HPT is not mutable because we only demand-load 
161                 -- external packages; the home package is eagerly 
162                 -- loaded, module by module, by the compilation manager.
163                 --      
164                 -- The HPT may contain modules compiled earlier by --make
165                 -- but not actually below the current module in the dependency
166                 -- graph.  (This changes a previous invariant: changed Jan 05.)
167         
168         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
169         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
170                 -- These are side-effected by compiling to reflect
171                 -- sucking in interface files.  They cache the state of
172                 -- external interface files, in effect.
173
174         hsc_FC  :: {-# UNPACK #-} !(IORef FinderCache)
175                 -- The finder's cache.  This caches the location of modules,
176                 -- so we don't have to search the filesystem multiple times.
177  }
178
179 hscEPS :: HscEnv -> IO ExternalPackageState
180 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
181
182 -- | A compilation target.
183 --
184 -- A target may be supplied with the actual text of the
185 -- module.  If so, use this instead of the file contents (this
186 -- is for use in an IDE where the file hasn't been saved by
187 -- the user yet).
188 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
189
190 data TargetId
191   = TargetModule Module
192         -- ^ A module name: search for the file
193   | TargetFile FilePath (Maybe Phase)
194         -- ^ A filename: preprocess & parse it to find the module name.
195         -- If specified, the Phase indicates how to compile this file
196         -- (which phase to start from).  Nothing indicates the starting phase
197         -- should be determined from the suffix of the filename.
198   deriving Eq
199
200 pprTarget :: Target -> SDoc
201 pprTarget (Target id _) = pprTargetId id
202
203 pprTargetId (TargetModule m) = ppr m
204 pprTargetId (TargetFile f _) = text f
205
206 type FinderCache = ModuleEnv FinderCacheEntry
207 type FinderCacheEntry = (ModLocation, Maybe (PackageConfig,Bool))
208         -- The finder's cache (see module Finder)
209
210 type HomePackageTable  = ModuleEnv HomeModInfo
211         -- Domain = modules in the home package
212 type PackageIfaceTable = ModuleEnv ModIface
213         -- Domain = modules in the imported packages
214
215 emptyHomePackageTable  = emptyModuleEnv
216 emptyPackageIfaceTable = emptyModuleEnv
217
218 data HomeModInfo 
219   = HomeModInfo { hm_iface    :: !ModIface,
220                   hm_details  :: !ModDetails,
221                   hm_linkable :: !(Maybe Linkable) }
222                 -- hm_linkable might be Nothing if:
223                 --   a) this is an .hs-boot module
224                 --   b) temporarily during compilation if we pruned away
225                 --      the old linkable because it was out of date.
226                 -- after a complete compilation (GHC.load), all hm_linkable
227                 -- fields in the HPT will be Just.
228 \end{code}
229
230 Simple lookups in the symbol table.
231
232 \begin{code}
233 lookupIface :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
234 -- We often have two IfaceTables, and want to do a lookup
235 lookupIface hpt pit mod
236   = case lookupModuleEnv hpt mod of
237         Just mod_info -> Just (hm_iface mod_info)
238         Nothing       -> lookupModuleEnv pit mod
239
240 lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
241 -- We often have two IfaceTables, and want to do a lookup
242 lookupIfaceByModule hpt pit mod
243   = case lookupModuleEnv hpt mod of
244         Just mod_info -> Just (hm_iface mod_info)
245         Nothing       -> lookupModuleEnv pit mod
246 \end{code}
247
248
249 \begin{code}
250 hptInstances :: HscEnv -> (Module -> Bool) -> [Instance]
251 -- Find all the instance declarations that are in modules imported 
252 -- by this one, directly or indirectly, and are in the Home Package Table
253 -- This ensures that we don't see instances from modules --make compiled 
254 -- before this one, but which are not below this one
255 hptInstances hsc_env want_this_module
256   = [ ispec 
257     | mod_info <- moduleEnvElts (hsc_HPT hsc_env)
258     , want_this_module (mi_module (hm_iface mod_info))
259     , ispec <- md_insts (hm_details mod_info) ]
260
261 hptRules :: HscEnv -> [(Module, IsBootInterface)] -> [CoreRule]
262 -- Get rules from modules "below" this one (in the dependency sense)
263 -- C.f Inst.hptInstances
264 hptRules hsc_env deps
265   | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
266   | otherwise
267   = let 
268         hpt = hsc_HPT hsc_env
269     in
270     [ rule
271     |   -- Find each non-hi-boot module below me
272       (mod, False) <- deps
273
274         -- Look it up in the HPT
275     , let mod_info = ASSERT( mod `elemModuleEnv` hpt )
276                      fromJust (lookupModuleEnv hpt mod)
277
278         -- And get its dfuns
279     , rule <- md_rules (hm_details mod_info) ]
280 \end{code}
281
282
283 %************************************************************************
284 %*                                                                      *
285 \subsection{Symbol tables and Module details}
286 %*                                                                      *
287 %************************************************************************
288
289 A @ModIface@ plus a @ModDetails@ summarises everything we know 
290 about a compiled module.  The @ModIface@ is the stuff *before* linking,
291 and can be written out to an interface file.  (The @ModDetails@ is after 
292 linking; it is the "linked" form of the mi_decls field.)
293
294 When we *read* an interface file, we also construct a @ModIface@ from it,
295 except that the mi_decls part is empty; when reading we consolidate
296 the declarations into a single indexed map in the @PersistentRenamerState@.
297
298 \begin{code}
299 data ModIface 
300    = ModIface {
301         mi_package  :: !PackageIdH,         -- Which package the module comes from
302         mi_module   :: !Module,
303         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
304
305         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
306         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
307
308         mi_deps     :: Dependencies,
309                 -- This is consulted for directly-imported modules,
310                 -- but not for anything else (hence lazy)
311
312                 -- Usages; kept sorted so that it's easy to decide
313                 -- whether to write a new iface file (changing usages
314                 -- doesn't affect the version of this module)
315         mi_usages   :: [Usage],
316                 -- NOT STRICT!  we read this field lazily from the interface file
317                 -- It is *only* consulted by the recompilation checker
318
319                 -- Exports
320                 -- Kept sorted by (mod,occ), to make version comparisons easier
321         mi_exports  :: ![IfaceExport],
322         mi_exp_vers :: !Version,        -- Version number of export list
323
324                 -- Fixities
325         mi_fixities :: [(OccName,Fixity)],
326                 -- NOT STRICT!  we read this field lazily from the interface file
327
328                 -- Deprecations
329         mi_deprecs  :: IfaceDeprecs,
330                 -- NOT STRICT!  we read this field lazily from the interface file
331
332                 -- Type, class and variable declarations
333                 -- The version of an Id changes if its fixity or deprecations change
334                 --      (as well as its type of course)
335                 -- Ditto data constructors, class operations, except that 
336                 -- the version of the parent class/tycon changes
337         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
338
339         mi_globals  :: !(Maybe GlobalRdrEnv),
340                 -- Binds all the things defined at the top level in
341                 -- the *original source* code for this module. which
342                 -- is NOT the same as mi_exports, nor mi_decls (which
343                 -- may contains declarations for things not actually
344                 -- defined by the user).  Used for GHCi and for inspecting
345                 -- the contents of modules via the GHC API only.
346                 --
347                 -- (We need the source file to figure out the
348                 -- top-level environment, if we didn't compile this module
349                 -- from source then this field contains Nothing).
350
351                 -- Instance declarations and rules
352         mi_insts     :: [IfaceInst],    -- Sorted
353         mi_rules     :: [IfaceRule],    -- Sorted
354         mi_rule_vers :: !Version,       -- Version number for rules and instances combined
355
356                 -- Cached environments for easy lookup
357                 -- These are computed (lazily) from other fields
358                 -- and are not put into the interface file
359         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
360         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
361         mi_ver_fn  :: OccName -> Maybe Version  -- Cached lookup for mi_decls
362                         -- The Nothing in mi_ver_fn means that the thing
363                         -- isn't in decls. It's useful to know that when
364                         -- seeing if we are up to date wrt the old interface
365      }
366
367 -- Should be able to construct ModDetails from mi_decls in ModIface
368 data ModDetails
369    = ModDetails {
370         -- The next three fields are created by the typechecker
371         md_exports  :: NameSet,
372         md_types    :: !TypeEnv,
373         md_insts    :: ![Instance],     -- Dfun-ids for the instances in this module
374         md_rules    :: ![CoreRule]      -- Domain may include Ids from other modules
375      }
376
377 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
378                                md_exports = emptyNameSet,
379                                md_insts = [],
380                                md_rules = [] }
381
382 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
383 -- There is only one ModGuts at any time, the one for the module
384 -- being compiled right now.  Once it is compiled, a ModIface and 
385 -- ModDetails are extracted and the ModGuts is dicarded.
386
387 data ModGuts
388   = ModGuts {
389         mg_module   :: !Module,
390         mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
391         mg_exports  :: !NameSet,        -- What it exports
392         mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
393         mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
394                                         --      generate initialisation code
395         mg_usages   :: ![Usage],        -- Version info for what it needed
396
397         mg_rdr_env  :: !GlobalRdrEnv,   -- Top-level lexical environment
398         mg_fix_env  :: !FixityEnv,      -- Fixity env, for things declared in this module
399         mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
400
401         mg_types    :: !TypeEnv,
402         mg_insts    :: ![Instance],     -- Instances 
403         mg_rules    :: ![CoreRule],     -- Rules from this module
404         mg_binds    :: ![CoreBind],     -- Bindings for this module
405         mg_foreign  :: !ForeignStubs
406     }
407
408 -- The ModGuts takes on several slightly different forms:
409 --
410 -- After simplification, the following fields change slightly:
411 --      mg_rules        Orphan rules only (local ones now attached to binds)
412 --      mg_binds        With rules attached
413
414
415 ---------------------------------------------------------
416 -- The Tidy pass forks the information about this module: 
417 --      * one lot goes to interface file generation (ModIface)
418 --        and later compilations (ModDetails)
419 --      * the other lot goes to code generation (CgGuts)
420 data CgGuts 
421   = CgGuts {
422         cg_module   :: !Module,
423
424         cg_tycons   :: [TyCon],         -- Algebraic data types (including ones that started life
425                                         -- as classes); generate constructors and info tables
426                                         -- Includes newtypes, just for the benefit of External Core
427
428         cg_binds    :: [CoreBind],      -- The tidied main bindings, including previously-implicit 
429                                         -- bindings for record and class selectors, and
430                                         -- data construtor wrappers.  
431                                         -- But *not* data constructor workers; reason: we
432                                         -- we regard them as part of the code-gen of tycons
433
434         cg_dir_imps :: ![Module],       -- Directly-imported modules; used to generate
435                                         -- initialisation code
436
437         cg_foreign  :: !ForeignStubs,   
438         cg_dep_pkgs :: ![PackageId]     -- Used to generate #includes for C code gen
439     }
440
441 -----------------------------------
442 data ModImports
443   = ModImports {
444         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
445                                                 -- Boolean is true if we imported the whole
446                                                 --      module (apart, perhaps, from hiding some)
447         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
448                                                 --      directly or indirectly
449         imp_home_names :: !NameSet              -- Home package things on which we depend,
450                                                 --      directly or indirectly
451     }
452
453 -----------------------------------
454 data ForeignStubs = NoStubs
455                   | ForeignStubs
456                         SDoc            -- Header file prototypes for
457                                         --      "foreign exported" functions
458                         SDoc            -- C stubs to use when calling
459                                         --      "foreign exported" functions
460                         [FastString]    -- Headers that need to be included
461                                         --      into C code generated for this module
462                         [Id]            -- Foreign-exported binders
463                                         --      we have to generate code to register these
464
465 \end{code}
466
467 \begin{code}
468 emptyModIface :: PackageIdH -> Module -> ModIface
469 emptyModIface pkg mod
470   = ModIface { mi_package  = pkg,
471                mi_module   = mod,
472                mi_mod_vers = initialVersion,
473                mi_orphan   = False,
474                mi_boot     = False,
475                mi_deps     = noDependencies,
476                mi_usages   = [],
477                mi_exports  = [],
478                mi_exp_vers = initialVersion,
479                mi_fixities = [],
480                mi_deprecs  = NoDeprecs,
481                mi_insts = [],
482                mi_rules = [],
483                mi_decls = [],
484                mi_globals  = Nothing,
485                mi_rule_vers = initialVersion,
486                mi_dep_fn = emptyIfaceDepCache,
487                mi_fix_fn = emptyIfaceFixCache,
488                mi_ver_fn = emptyIfaceVerCache
489     }           
490 \end{code}
491
492
493 %************************************************************************
494 %*                                                                      *
495 \subsection{The interactive context}
496 %*                                                                      *
497 %************************************************************************
498
499 \begin{code}
500 data InteractiveContext 
501   = InteractiveContext { 
502         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
503                                         -- these modules
504
505         ic_exports :: [Module],         -- Include just the exports of these
506                                         -- modules
507
508         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
509                                         -- ic_toplev_scope and ic_exports
510
511         ic_rn_local_env :: LocalRdrEnv, -- Lexical context for variables bound
512                                         -- during interaction
513
514         ic_type_env :: TypeEnv          -- Ditto for types
515     }
516
517 emptyInteractiveContext
518   = InteractiveContext { ic_toplev_scope = [],
519                          ic_exports = [],
520                          ic_rn_gbl_env = emptyGlobalRdrEnv,
521                          ic_rn_local_env = emptyLocalRdrEnv,
522                          ic_type_env = emptyTypeEnv }
523
524 icPrintUnqual :: InteractiveContext -> PrintUnqualified
525 icPrintUnqual ictxt = unQualInScope (ic_rn_gbl_env ictxt)
526 \end{code}
527
528 @unQualInScope@ returns a function that takes a @Name@ and tells whether
529 its unqualified name is in scope.  This is put as a boolean flag in
530 the @Name@'s provenance to guide whether or not to print the name qualified
531 in error messages.
532
533 \begin{code}
534 unQualInScope :: GlobalRdrEnv -> PrintUnqualified
535 -- True if 'f' is in scope, and has only one binding,
536 -- and the thing it is bound to is the name we are looking for
537 -- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
538 --
539 -- [Out of date] Also checks for built-in syntax, which is always 'in scope'
540 unQualInScope env mod occ
541   = case lookupGRE_RdrName (mkRdrUnqual occ) env of
542         [gre] -> nameModule (gre_name gre) == mod
543         other -> False
544 \end{code}
545
546
547 %************************************************************************
548 %*                                                                      *
549                 TyThing
550 %*                                                                      *
551 %************************************************************************
552
553 \begin{code}
554 implicitTyThings :: TyThing -> [TyThing]
555 implicitTyThings (AnId id)   = []
556
557         -- For type constructors, add the data cons (and their extras),
558         -- and the selectors and generic-programming Ids too
559         --
560         -- Newtypes don't have a worker Id, so don't generate that?
561 implicitTyThings (ATyCon tc) = map AnId (tyConSelIds tc) ++ 
562                                concatMap (extras_plus . ADataCon) (tyConDataCons tc)
563                      
564         -- For classes, add the class TyCon too (and its extras)
565         -- and the class selector Ids
566 implicitTyThings (AClass cl) = map AnId (classSelIds cl) ++
567                                extras_plus (ATyCon (classTyCon cl))
568                          
569
570         -- For data cons add the worker and wrapper (if any)
571 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
572
573 extras_plus thing = thing : implicitTyThings thing
574
575 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
576 extendTypeEnvWithIds env ids
577   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
578 \end{code}
579
580 %************************************************************************
581 %*                                                                      *
582                 TypeEnv
583 %*                                                                      *
584 %************************************************************************
585
586 \begin{code}
587 type TypeEnv = NameEnv TyThing
588
589 emptyTypeEnv   :: TypeEnv
590 typeEnvElts    :: TypeEnv -> [TyThing]
591 typeEnvClasses :: TypeEnv -> [Class]
592 typeEnvTyCons  :: TypeEnv -> [TyCon]
593 typeEnvIds     :: TypeEnv -> [Id]
594 lookupTypeEnv  :: TypeEnv -> Name -> Maybe TyThing
595
596 emptyTypeEnv       = emptyNameEnv
597 typeEnvElts    env = nameEnvElts env
598 typeEnvClasses env = [cl | AClass cl <- typeEnvElts env]
599 typeEnvTyCons  env = [tc | ATyCon tc <- typeEnvElts env] 
600 typeEnvIds     env = [id | AnId id   <- typeEnvElts env] 
601
602 mkTypeEnv :: [TyThing] -> TypeEnv
603 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
604                 
605 lookupTypeEnv = lookupNameEnv
606
607 -- Extend the type environment
608 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
609 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
610
611 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
612 extendTypeEnvList env things = foldl extendTypeEnv env things
613 \end{code}
614
615 \begin{code}
616 lookupType :: HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
617 lookupType hpt pte name
618   = case lookupModuleEnv hpt (nameModule name) of
619         Just details -> lookupNameEnv (md_types (hm_details details)) name
620         Nothing      -> lookupNameEnv pte name
621 \end{code}
622
623
624 \begin{code}
625 tyThingTyCon (ATyCon tc) = tc
626 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
627
628 tyThingClass (AClass cls) = cls
629 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
630
631 tyThingDataCon (ADataCon dc) = dc
632 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
633
634 tyThingId (AnId id) = id
635 tyThingId other     = pprPanic "tyThingId" (ppr other)
636 \end{code}
637
638 %************************************************************************
639 %*                                                                      *
640 \subsection{Auxiliary types}
641 %*                                                                      *
642 %************************************************************************
643
644 These types are defined here because they are mentioned in ModDetails,
645 but they are mostly elaborated elsewhere
646
647 \begin{code}
648 mkIfaceVerCache :: [(Version,IfaceDecl)] -> OccName -> Maybe Version
649 mkIfaceVerCache pairs 
650   = \occ -> lookupOccEnv env occ
651   where
652     env = foldl add emptyOccEnv pairs
653     add env (v,d) = extendOccEnv env (ifName d) v
654
655 emptyIfaceVerCache :: OccName -> Maybe Version
656 emptyIfaceVerCache occ = Nothing
657
658 ------------------ Deprecations -------------------------
659 data Deprecs a
660   = NoDeprecs
661   | DeprecAll DeprecTxt -- Whole module deprecated
662   | DeprecSome a        -- Some specific things deprecated
663   deriving( Eq )
664
665 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
666 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
667         -- Keep the OccName so we can flatten the NameEnv to
668         -- get an IfaceDeprecs from a Deprecations
669         -- Only an OccName is needed, because a deprecation always
670         -- applies to things defined in the module in which the
671         -- deprecation appears.
672
673 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
674 mkIfaceDepCache NoDeprecs         = \n -> Nothing
675 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
676 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
677
678 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
679 emptyIfaceDepCache n = Nothing
680
681 lookupDeprec :: Deprecations -> Name -> Maybe DeprecTxt
682 lookupDeprec NoDeprecs        name = Nothing
683 lookupDeprec (DeprecAll  txt) name = Just txt
684 lookupDeprec (DeprecSome env) name = case lookupNameEnv env name of
685                                             Just (_, txt) -> Just txt
686                                             Nothing       -> Nothing
687
688 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
689 plusDeprecs d NoDeprecs = d
690 plusDeprecs NoDeprecs d = d
691 plusDeprecs d (DeprecAll t) = DeprecAll t
692 plusDeprecs (DeprecAll t) d = DeprecAll t
693 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
694 \end{code}
695
696
697 \begin{code}
698 type Avails       = [AvailInfo]
699 type AvailInfo    = GenAvailInfo Name
700 type RdrAvailInfo = GenAvailInfo OccName
701
702 data GenAvailInfo name  = Avail name     -- An ordinary identifier
703                         | AvailTC name   -- The name of the type or class
704                                   [name] -- The available pieces of type/class.
705                                          -- NB: If the type or class is itself
706                                          -- to be in scope, it must be in this list.
707                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
708                         deriving( Eq )
709                         -- Equality used when deciding if the interface has changed
710
711 type IfaceExport = (Module, [GenAvailInfo OccName])
712
713 availsToNameSet :: [AvailInfo] -> NameSet
714 availsToNameSet avails = foldl add emptyNameSet avails
715                        where
716                          add set avail = addListToNameSet set (availNames avail)
717
718 availName :: GenAvailInfo name -> name
719 availName (Avail n)     = n
720 availName (AvailTC n _) = n
721
722 availNames :: GenAvailInfo name -> [name]
723 availNames (Avail n)      = [n]
724 availNames (AvailTC n ns) = ns
725
726 instance Outputable n => Outputable (GenAvailInfo n) where
727    ppr = pprAvail
728
729 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
730 pprAvail (AvailTC n ns) = ppr n <> case {- filter (/= n) -} ns of
731                                         []  -> empty
732                                         ns' -> braces (hsep (punctuate comma (map ppr ns')))
733
734 pprAvail (Avail n) = ppr n
735 \end{code}
736
737 \begin{code}
738 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
739 mkIfaceFixCache pairs 
740   = \n -> lookupOccEnv env n `orElse` defaultFixity
741   where
742    env = mkOccEnv pairs
743
744 emptyIfaceFixCache :: OccName -> Fixity
745 emptyIfaceFixCache n = defaultFixity
746
747 -- This fixity environment is for source code only
748 type FixityEnv = NameEnv FixItem
749
750 -- We keep the OccName in the range so that we can generate an interface from it
751 data FixItem = FixItem OccName Fixity SrcSpan
752
753 instance Outputable FixItem where
754   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
755
756 emptyFixityEnv :: FixityEnv
757 emptyFixityEnv = emptyNameEnv
758
759 lookupFixity :: FixityEnv -> Name -> Fixity
760 lookupFixity env n = case lookupNameEnv env n of
761                         Just (FixItem _ fix _) -> fix
762                         Nothing                -> defaultFixity
763 \end{code}
764
765
766 %************************************************************************
767 %*                                                                      *
768 \subsection{WhatsImported}
769 %*                                                                      *
770 %************************************************************************
771
772 \begin{code}
773 type WhetherHasOrphans   = Bool
774         -- An "orphan" is 
775         --      * an instance decl in a module other than the defn module for 
776         --              one of the tycons or classes in the instance head
777         --      * a transformation rule in a module other than the one defining
778         --              the function in the head of the rule.
779
780 type IsBootInterface = Bool
781
782 -- Dependency info about modules and packages below this one
783 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
784 --
785 -- Invariant: the dependencies of a module M never includes M
786 -- Invariant: the lists are unordered, with no duplicates
787 data Dependencies
788   = Deps { dep_mods  :: [(Module,IsBootInterface)],     -- Home-package module dependencies
789            dep_pkgs  :: [PackageId],                    -- External package dependencies
790            dep_orphs :: [Module] }                      -- Orphan modules (whether home or external pkg)
791   deriving( Eq )
792         -- Equality used only for old/new comparison in MkIface.addVersionInfo
793
794 noDependencies :: Dependencies
795 noDependencies = Deps [] [] []
796           
797 data Usage
798   = Usage { usg_name     :: Module,                     -- Name of the module
799             usg_mod      :: Version,                    -- Module version
800             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
801             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
802             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
803                                                         -- modules this will always be initialVersion)
804     }       deriving( Eq )
805         -- This type doesn't let you say "I imported f but none of the rules in
806         -- the module". If you use anything in the module you get its rule version
807         -- So if the rules change, you'll recompile, even if you don't use them.
808         -- This is easy to implement, and it's safer: you might not have used the rules last
809         -- time round, but if someone has added a new rule you might need it this time
810
811         -- The export list field is (Just v) if we depend on the export list:
812         --      i.e. we imported the module without saying exactly what we imported
813         -- We need to recompile if the module exports changes, because we might
814         -- now have a name clash in the importing module.
815 \end{code}
816
817
818 %************************************************************************
819 %*                                                                      *
820                 The External Package State
821 %*                                                                      *
822 %************************************************************************
823
824 \begin{code}
825 type PackageTypeEnv  = TypeEnv
826 type PackageRuleBase = RuleBase
827 type PackageInstEnv  = InstEnv
828
829 data ExternalPackageState
830   = EPS {
831         eps_is_boot :: !(ModuleEnv (Module, IsBootInterface)),
832                 -- In OneShot mode (only), home-package modules accumulate in the
833                 -- external package state, and are sucked in lazily.
834                 -- For these home-pkg modules (only) we need to record which are
835                 -- boot modules.  We set this field after loading all the 
836                 -- explicitly-imported interfaces, but before doing anything else
837                 --
838                 -- The Module part is not necessary, but it's useful for
839                 -- debug prints, and it's convenient because this field comes
840                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
841
842         eps_PIT :: !PackageIfaceTable,
843                 -- The ModuleIFaces for modules in external packages
844                 -- whose interfaces we have opened
845                 -- The declarations in these interface files are held in
846                 -- eps_decls, eps_inst_env, eps_rules (below), not in the 
847                 -- mi_decls fields of the iPIT.  
848                 -- What _is_ in the iPIT is:
849                 --      * The Module 
850                 --      * Version info
851                 --      * Its exports
852                 --      * Fixities
853                 --      * Deprecations
854
855         eps_PTE :: !PackageTypeEnv,             -- Domain = external-package modules
856
857         eps_inst_env :: !PackageInstEnv,        -- The total InstEnv accumulated from
858                                                 --   all the external-package modules
859         eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
860
861         eps_stats :: !EpsStats
862   }
863
864 -- "In" means read from iface files
865 -- "Out" means actually sucked in and type-checked
866 data EpsStats = EpsStats { n_ifaces_in
867                          , n_decls_in, n_decls_out 
868                          , n_rules_in, n_rules_out
869                          , n_insts_in, n_insts_out :: !Int }
870
871 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
872 -- Add stats for one newly-read interface
873 addEpsInStats stats n_decls n_insts n_rules
874   = stats { n_ifaces_in = n_ifaces_in stats + 1
875           , n_decls_in  = n_decls_in stats + n_decls
876           , n_insts_in  = n_insts_in stats + n_insts
877           , n_rules_in  = n_rules_in stats + n_rules }
878 \end{code}
879
880 The NameCache makes sure that there is just one Unique assigned for
881 each original name; i.e. (module-name, occ-name) pair.  The Name is
882 always stored as a Global, and has the SrcLoc of its binding location.
883 Actually that's not quite right.  When we first encounter the original
884 name, we might not be at its binding site (e.g. we are reading an
885 interface file); so we give it 'noSrcLoc' then.  Later, when we find
886 its binding site, we fix it up.
887
888 \begin{code}
889 data NameCache
890  = NameCache {  nsUniqs :: UniqSupply,
891                 -- Supply of uniques
892                 nsNames :: OrigNameCache,
893                 -- Ensures that one original name gets one unique
894                 nsIPs   :: OrigIParamCache
895                 -- Ensures that one implicit parameter name gets one unique
896    }
897
898 type OrigNameCache   = ModuleEnv (OccEnv Name)
899 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
900 \end{code}
901
902
903
904 %************************************************************************
905 %*                                                                      *
906                 The module graph and ModSummary type
907         A ModSummary is a node in the compilation manager's
908         dependency graph, and it's also passed to hscMain
909 %*                                                                      *
910 %************************************************************************
911
912 A ModuleGraph contains all the nodes from the home package (only).  
913 There will be a node for each source module, plus a node for each hi-boot
914 module.
915
916 \begin{code}
917 type ModuleGraph = [ModSummary]  -- The module graph, 
918                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
919
920 emptyMG :: ModuleGraph
921 emptyMG = []
922
923 -- The nodes of the module graph are
924 --      EITHER a regular Haskell source module
925 --      OR     a hi-boot source module
926
927 data ModSummary
928    = ModSummary {
929         ms_mod       :: Module,                 -- Name of the module
930         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
931         ms_location  :: ModLocation,            -- Location
932         ms_hs_date   :: ClockTime,              -- Timestamp of source file
933         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
934         ms_srcimps   :: [Module],               -- Source imports
935         ms_imps      :: [Module],               -- Non-source imports
936         ms_hspp_file :: Maybe FilePath,         -- Filename of preprocessed source,
937                                                 -- once we have preprocessed it.
938         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
939      }
940
941 -- The ModLocation contains both the original source filename and the
942 -- filename of the cleaned-up source file after all preprocessing has been
943 -- done.  The point is that the summariser will have to cpp/unlit/whatever
944 -- all files anyway, and there's no point in doing this twice -- just 
945 -- park the result in a temp file, put the name of it in the location,
946 -- and let @compile@ read from that file on the way back up.
947
948 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
949 -- the ms_hs_date and imports can, of course, change
950
951 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
952 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
953 msHiFilePath  ms = ml_hi_file  (ms_location ms)
954 msObjFilePath ms = ml_obj_file (ms_location ms)
955
956 isBootSummary :: ModSummary -> Bool
957 isBootSummary ms = isHsBoot (ms_hsc_src ms)
958
959 instance Outputable ModSummary where
960    ppr ms
961       = sep [text "ModSummary {",
962              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
963                           text "ms_mod =" <+> ppr (ms_mod ms) 
964                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
965                           text "ms_imps =" <+> ppr (ms_imps ms),
966                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
967              char '}'
968             ]
969
970 showModMsg :: Bool -> ModSummary -> String
971 showModMsg use_object mod_summary
972   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
973                     char '(', text (msHsFilePath mod_summary) <> comma,
974                     if use_object then text (msObjFilePath mod_summary)
975                               else text "interpreted",
976                     char ')'])
977  where 
978     mod     = ms_mod mod_summary 
979     mod_str = moduleUserString mod ++ hscSourceString (ms_hsc_src mod_summary)
980 \end{code}
981
982
983 %************************************************************************
984 %*                                                                      *
985 \subsection{Linkable stuff}
986 %*                                                                      *
987 %************************************************************************
988
989 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
990 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
991
992 \begin{code}
993 data Linkable = LM {
994   linkableTime     :: ClockTime,        -- Time at which this linkable was built
995                                         -- (i.e. when the bytecodes were produced,
996                                         --       or the mod date on the files)
997   linkableModule   :: Module,           -- Should be Module, but see below
998   linkableUnlinked :: [Unlinked]
999  }
1000
1001 isObjectLinkable :: Linkable -> Bool
1002 isObjectLinkable l = all isObject (linkableUnlinked l)
1003
1004 instance Outputable Linkable where
1005    ppr (LM when_made mod unlinkeds)
1006       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1007         $$ nest 3 (ppr unlinkeds)
1008
1009 -------------------------------------------
1010 data Unlinked
1011    = DotO FilePath
1012    | DotA FilePath
1013    | DotDLL FilePath
1014    | BCOs CompiledByteCode
1015
1016 #ifndef GHCI
1017 data CompiledByteCode = NoByteCode
1018 #endif
1019
1020 instance Outputable Unlinked where
1021    ppr (DotO path)   = text "DotO" <+> text path
1022    ppr (DotA path)   = text "DotA" <+> text path
1023    ppr (DotDLL path) = text "DotDLL" <+> text path
1024 #ifdef GHCI
1025    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1026 #else
1027    ppr (BCOs bcos)   = text "No byte code"
1028 #endif
1029
1030 isObject (DotO _)   = True
1031 isObject (DotA _)   = True
1032 isObject (DotDLL _) = True
1033 isObject _          = False
1034
1035 isInterpretable = not . isObject
1036
1037 nameOfObject (DotO fn)   = fn
1038 nameOfObject (DotA fn)   = fn
1039 nameOfObject (DotDLL fn) = fn
1040
1041 byteCodeOfObject (BCOs bc) = bc
1042 \end{code}
1043
1044
1045