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