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