Improved VectInfo
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
1 %
2 % (c) The University of Glasgow, 2006
3 %
4 \section[HscTypes]{Types for the per-module compiler}
5
6 \begin{code}
7 module HscTypes ( 
8         -- * Sessions and compilation state
9         Session(..), withSession, modifySession, 
10         HscEnv(..), hscEPS,
11         FinderCache, FindResult(..), ModLocationCache,
12         Target(..), TargetId(..), pprTarget, pprTargetId,
13         ModuleGraph, emptyMG,
14
15         ModDetails(..), emptyModDetails,
16         ModGuts(..), CgGuts(..), ModImports(..), ForeignStubs(..),
17
18         ModSummary(..), ms_mod_name, showModMsg, isBootSummary,
19         msHsFilePath, msHiFilePath, msObjFilePath, 
20
21         HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
22         
23         HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
24         hptInstances, hptRules, hptVectInfo,
25
26         ExternalPackageState(..), EpsStats(..), addEpsInStats,
27         PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
28         lookupIfaceByModule, emptyModIface,
29
30         InteractiveContext(..), emptyInteractiveContext, 
31         icPrintUnqual, mkPrintUnqualified, extendInteractiveContext,
32
33         ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
34         emptyIfaceDepCache,
35
36         Deprecs(..), IfaceDeprecs,
37
38         FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
39
40         implicitTyThings, isImplicitTyThing,
41
42         TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId,
43         TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv,
44         extendTypeEnv, extendTypeEnvList, extendTypeEnvWithIds, lookupTypeEnv,
45         typeEnvElts, typeEnvClasses, typeEnvTyCons, typeEnvIds,
46         typeEnvDataCons,
47
48         WhetherHasOrphans, IsBootInterface, Usage(..), 
49         Dependencies(..), noDependencies,
50         NameCache(..), OrigNameCache, OrigIParamCache,
51         Avails, availsToNameSet, availsToNameEnv, availName, availNames,
52         GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
53         IfaceExport,
54
55         Deprecations, DeprecTxt, plusDeprecs,
56
57         PackageInstEnv, PackageRuleBase,
58
59         -- Linker stuff
60         Linkable(..), isObjectLinkable,
61         Unlinked(..), CompiledByteCode,
62         isObject, nameOfObject, isInterpretable, byteCodeOfObject,
63         HpcInfo(..), noHpcInfo,
64
65         -- Breakpoints
66         ModBreaks (..), BreakIndex, emptyModBreaks,
67
68         -- Vectorisation information
69         VectInfo(..), IfaceVectInfo(..), noVectInfo, plusVectInfo, 
70         noIfaceVectInfo
71     ) where
72
73 #include "HsVersions.h"
74
75 #ifdef GHCI
76 import ByteCodeAsm      ( CompiledByteCode )
77 import {-# SOURCE #-}  InteractiveEval ( Resume )
78 #endif
79
80 import RdrName          ( GlobalRdrEnv, emptyGlobalRdrEnv, GlobalRdrElt(..), 
81                           unQualOK, ImpDeclSpec(..), Provenance(..),
82                           ImportSpec(..), lookupGlobalRdrEnv )
83 import Name             ( Name, NamedThing, getName, nameOccName, nameModule )
84 import NameEnv
85 import NameSet  
86 import OccName          ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
87                           extendOccEnv )
88 import Module
89 import InstEnv          ( InstEnv, Instance )
90 import FamInstEnv       ( FamInstEnv, FamInst )
91 import Rules            ( RuleBase )
92 import CoreSyn          ( CoreBind )
93 import VarEnv
94 import VarSet
95 import Var
96 import Id
97 import Type             ( TyThing(..) )
98
99 import Class            ( Class, classSelIds, classATs, classTyCon )
100 import TyCon
101 import DataCon          ( DataCon, dataConImplicitIds )
102 import PrelNames        ( gHC_PRIM )
103 import Packages         ( PackageId )
104 import DynFlags         ( DynFlags(..), isOneShot, HscTarget (..) )
105 import DriverPhases     ( HscSource(..), isHsBoot, hscSourceString, Phase )
106 import BasicTypes       ( Version, initialVersion, IPName, 
107                           Fixity, defaultFixity, DeprecTxt )
108 import IfaceSyn
109 import FiniteMap        ( FiniteMap )
110 import CoreSyn          ( CoreRule )
111 import Maybes           ( orElse, expectJust, catMaybes, seqMaybe )
112 import Outputable
113 import BreakArray
114 import SrcLoc           ( SrcSpan, Located )
115 import UniqFM           ( lookupUFM, eltsUFM, emptyUFM )
116 import UniqSupply       ( UniqSupply )
117 import FastString       ( FastString )
118
119 import StringBuffer     ( StringBuffer )
120
121 import System.Time      ( ClockTime )
122 import Data.IORef
123 import Data.Array       ( Array, array )
124 \end{code}
125
126
127 %************************************************************************
128 %*                                                                      *
129 \subsection{Compilation environment}
130 %*                                                                      *
131 %************************************************************************
132
133
134 \begin{code}
135 -- | The Session is a handle to the complete state of a compilation
136 -- session.  A compilation session consists of a set of modules
137 -- constituting the current program or library, the context for
138 -- interactive evaluation, and various caches.
139 newtype Session = Session (IORef HscEnv)
140
141 withSession :: Session -> (HscEnv -> IO a) -> IO a
142 withSession (Session ref) f = do h <- readIORef ref; f h
143
144 modifySession :: Session -> (HscEnv -> HscEnv) -> IO ()
145 modifySession (Session ref) f = do h <- readIORef ref; writeIORef ref $! f h
146 \end{code}
147
148 HscEnv is like Session, except that some of the fields are immutable.
149 An HscEnv is used to compile a single module from plain Haskell source
150 code (after preprocessing) to either C, assembly or C--.  Things like
151 the module graph don't change during a single compilation.
152
153 Historical note: "hsc" used to be the name of the compiler binary,
154 when there was a separate driver and compiler.  To compile a single
155 module, the driver would invoke hsc on the source code... so nowadays
156 we think of hsc as the layer of the compiler that deals with compiling
157 a single module.
158
159 \begin{code}
160 data HscEnv 
161   = HscEnv { 
162         hsc_dflags :: DynFlags,
163                 -- The dynamic flag settings
164
165         hsc_targets :: [Target],
166                 -- The targets (or roots) of the current session
167
168         hsc_mod_graph :: ModuleGraph,
169                 -- The module graph of the current session
170
171         hsc_IC :: InteractiveContext,
172                 -- The context for evaluating interactive statements
173
174         hsc_HPT    :: HomePackageTable,
175                 -- The home package table describes already-compiled
176                 -- home-packge modules, *excluding* the module we 
177                 -- are compiling right now.
178                 -- (In one-shot mode the current module is the only
179                 --  home-package module, so hsc_HPT is empty.  All other
180                 --  modules count as "external-package" modules.
181                 --  However, even in GHCi mode, hi-boot interfaces are
182                 --  demand-loadeded into the external-package table.)
183                 --
184                 -- hsc_HPT is not mutable because we only demand-load 
185                 -- external packages; the home package is eagerly 
186                 -- loaded, module by module, by the compilation manager.
187                 --      
188                 -- The HPT may contain modules compiled earlier by --make
189                 -- but not actually below the current module in the dependency
190                 -- graph.  (This changes a previous invariant: changed Jan 05.)
191         
192         hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
193         hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
194                 -- These are side-effected by compiling to reflect
195                 -- sucking in interface files.  They cache the state of
196                 -- external interface files, in effect.
197
198         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
199         hsc_MLC  :: {-# UNPACK #-} !(IORef ModLocationCache),
200                 -- The finder's cache.  This caches the location of modules,
201                 -- so we don't have to search the filesystem multiple times.
202
203         hsc_global_rdr_env :: GlobalRdrEnv,
204         hsc_global_type_env :: TypeEnv
205  }
206
207 hscEPS :: HscEnv -> IO ExternalPackageState
208 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
209
210 -- | A compilation target.
211 --
212 -- A target may be supplied with the actual text of the
213 -- module.  If so, use this instead of the file contents (this
214 -- is for use in an IDE where the file hasn't been saved by
215 -- the user yet).
216 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
217
218 data TargetId
219   = TargetModule ModuleName
220         -- ^ A module name: search for the file
221   | TargetFile FilePath (Maybe Phase)
222         -- ^ A filename: preprocess & parse it to find the module name.
223         -- If specified, the Phase indicates how to compile this file
224         -- (which phase to start from).  Nothing indicates the starting phase
225         -- should be determined from the suffix of the filename.
226   deriving Eq
227
228 pprTarget :: Target -> SDoc
229 pprTarget (Target id _) = pprTargetId id
230
231 instance Outputable Target where
232     ppr = pprTarget
233
234 pprTargetId (TargetModule m) = ppr m
235 pprTargetId (TargetFile f _) = text f
236
237 instance Outputable TargetId where
238     ppr = pprTargetId
239
240 type HomePackageTable  = ModuleNameEnv HomeModInfo
241         -- Domain = modules in the home package
242         -- "home" package name cached here for convenience
243 type PackageIfaceTable = ModuleEnv ModIface
244         -- Domain = modules in the imported packages
245
246 emptyHomePackageTable  = emptyUFM
247 emptyPackageIfaceTable = emptyModuleEnv
248
249 data HomeModInfo 
250   = HomeModInfo { hm_iface    :: !ModIface,
251                   hm_details  :: !ModDetails,
252                   hm_linkable :: !(Maybe Linkable) }
253                 -- hm_linkable might be Nothing if:
254                 --   a) this is an .hs-boot module
255                 --   b) temporarily during compilation if we pruned away
256                 --      the old linkable because it was out of date.
257                 -- after a complete compilation (GHC.load), all hm_linkable
258                 -- fields in the HPT will be Just.
259                 --
260                 -- When re-linking a module (hscNoRecomp), we construct
261                 -- the HomModInfo by building a new ModDetails from the
262                 -- old ModIface (only).
263
264 -- | Find the 'ModIface' for a 'Module'
265 lookupIfaceByModule
266         :: DynFlags
267         -> HomePackageTable
268         -> PackageIfaceTable
269         -> Module
270         -> Maybe ModIface
271 lookupIfaceByModule dflags hpt pit mod
272   | modulePackageId mod == thisPackage dflags
273   =     -- The module comes from the home package, so look first
274         -- in the HPT.  If it's not from the home package it's wrong to look
275         -- in the HPT, because the HPT is indexed by *ModuleName* not Module
276     fmap hm_iface (lookupUFM hpt (moduleName mod)) 
277     `seqMaybe` lookupModuleEnv pit mod
278
279   | otherwise = lookupModuleEnv pit mod         -- Look in PIT only 
280
281 -- If the module does come from the home package, why do we look in the PIT as well?
282 -- (a) In OneShot mode, even home-package modules accumulate in the PIT
283 -- (b) Even in Batch (--make) mode, there is *one* case where a home-package
284 --     module is in the PIT, namely GHC.Prim when compiling the base package.
285 -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a packake
286 -- of its own, but it doesn't seem worth the bother.
287 \end{code}
288
289
290 \begin{code}
291 hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
292 -- Find all the instance declarations (of classes and families) that are in
293 -- modules imported by this one, directly or indirectly, and are in the Home
294 -- Package Table.  This ensures that we don't see instances from modules --make
295 -- compiled before this one, but which are not below this one.
296 hptInstances hsc_env want_this_module
297   = let (insts, famInsts) = unzip
298           [ (md_insts details, md_fam_insts details)
299           | mod_info <- eltsUFM (hsc_HPT hsc_env)
300           , want_this_module (moduleName (mi_module (hm_iface mod_info)))
301           , let details = hm_details mod_info ]
302     in
303     (concat insts, concat famInsts)
304
305 hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
306 -- Get rules from modules "below" this one (in the dependency sense)
307 -- C.f Inst.hptInstances
308 hptRules hsc_env deps
309   | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
310   | otherwise
311   = let 
312         hpt = hsc_HPT hsc_env
313     in
314     [ rule
315     |   -- Find each non-hi-boot module below me
316       (mod, False) <- deps
317
318         -- unsavoury: when compiling the base package with --make, we
319         -- sometimes try to look up RULES for GHC.Prim.  GHC.Prim won't
320         -- be in the HPT, because we never compile it; it's in the EPT
321         -- instead.  ToDo: clean up, and remove this slightly bogus
322         -- filter:
323     , mod /= moduleName gHC_PRIM
324
325         -- Look it up in the HPT
326     , let rules = case lookupUFM hpt mod of
327                     Just info -> md_rules (hm_details info)
328                     Nothing -> pprTrace "WARNING in hptRules" msg [] 
329           msg = vcat [ptext SLIT("missing module") <+> ppr mod,
330                       ptext SLIT("Probable cause: out-of-date interface files")]
331                         -- This really shouldn't happen, but see Trac #962
332
333         -- And get its dfuns
334     , rule <- rules ]
335
336 hptVectInfo :: HscEnv -> VectInfo
337 -- Get the combined VectInfo of all modules in the home package table.  In
338 -- contrast to instances and rules, we don't care whether the modules are
339 -- "below" or us.  The VectInfo of those modules not "below" us does not
340 -- affect the compilation of the current module.
341 hptVectInfo hsc_env 
342   = foldr plusVectInfo noVectInfo [ md_vect_info (hm_details mod_info)
343                                   | mod_info <- eltsUFM (hsc_HPT hsc_env)]
344 \end{code}
345
346 %************************************************************************
347 %*                                                                      *
348 \subsection{The Finder cache}
349 %*                                                                      *
350 %************************************************************************
351
352 \begin{code}
353 -- | The 'FinderCache' maps home module names to the result of
354 -- searching for that module.  It records the results of searching for
355 -- modules along the search path.  On @:load@, we flush the entire
356 -- contents of this cache.
357 --
358 -- Although the @FinderCache@ range is 'FindResult' for convenience ,
359 -- in fact it will only ever contain 'Found' or 'NotFound' entries.
360 --
361 type FinderCache = ModuleNameEnv FindResult
362
363 -- | The result of searching for an imported module.
364 data FindResult
365   = Found ModLocation Module
366         -- the module was found
367   | NoPackage PackageId
368         -- the requested package was not found
369   | FoundMultiple [PackageId]
370         -- *error*: both in multiple packages
371   | PackageHidden PackageId
372         -- for an explicit source import: the package containing the module is
373         -- not exposed.
374   | ModuleHidden  PackageId
375         -- for an explicit source import: the package containing the module is
376         -- exposed, but the module itself is hidden.
377   | NotFound [FilePath] (Maybe PackageId)
378         -- the module was not found, the specified places were searched
379   | NotFoundInPackage PackageId
380         -- the module was not found in this package
381
382 -- | Cache that remembers where we found a particular module.  Contains both
383 -- home modules and package modules.  On @:load@, only home modules are
384 -- purged from this cache.
385 type ModLocationCache = ModuleEnv ModLocation
386 \end{code}
387
388 %************************************************************************
389 %*                                                                      *
390 \subsection{Symbol tables and Module details}
391 %*                                                                      *
392 %************************************************************************
393
394 A @ModIface@ plus a @ModDetails@ summarises everything we know 
395 about a compiled module.  The @ModIface@ is the stuff *before* linking,
396 and can be written out to an interface file.  (The @ModDetails@ is after 
397 linking; it is the "linked" form of the mi_decls field.)
398
399 When we *read* an interface file, we also construct a @ModIface@ from it,
400 except that the mi_decls part is empty; when reading we consolidate
401 the declarations into a single indexed map in the @PersistentRenamerState@.
402
403 \begin{code}
404 data ModIface 
405    = ModIface {
406         mi_module   :: !Module,
407         mi_mod_vers :: !Version,            -- Module version: changes when anything changes
408
409         mi_orphan   :: !WhetherHasOrphans,  -- Whether this module has orphans
410         mi_finsts   :: !WhetherHasFamInst,  -- Whether module has family insts
411         mi_boot     :: !IsBootInterface,    -- Read from an hi-boot file?
412
413         mi_deps     :: Dependencies,
414                 -- This is consulted for directly-imported modules,
415                 -- but not for anything else (hence lazy)
416
417                 -- Usages; kept sorted so that it's easy to decide
418                 -- whether to write a new iface file (changing usages
419                 -- doesn't affect the version of this module)
420         mi_usages   :: [Usage],
421                 -- NOT STRICT!  we read this field lazily from the interface file
422                 -- It is *only* consulted by the recompilation checker
423
424                 -- Exports
425                 -- Kept sorted by (mod,occ), to make version comparisons easier
426         mi_exports  :: ![IfaceExport],
427         mi_exp_vers :: !Version,        -- Version number of export list
428
429                 -- Fixities
430         mi_fixities :: [(OccName,Fixity)],
431                 -- NOT STRICT!  we read this field lazily from the interface file
432
433                 -- Deprecations
434         mi_deprecs  :: IfaceDeprecs,
435                 -- NOT STRICT!  we read this field lazily from the interface file
436
437                 -- Type, class and variable declarations
438                 -- The version of an Id changes if its fixity or deprecations change
439                 --      (as well as its type of course)
440                 -- Ditto data constructors, class operations, except that 
441                 -- the version of the parent class/tycon changes
442         mi_decls :: [(Version,IfaceDecl)],      -- Sorted
443
444         mi_globals  :: !(Maybe GlobalRdrEnv),
445                 -- Binds all the things defined at the top level in
446                 -- the *original source* code for this module. which
447                 -- is NOT the same as mi_exports, nor mi_decls (which
448                 -- may contains declarations for things not actually
449                 -- defined by the user).  Used for GHCi and for inspecting
450                 -- the contents of modules via the GHC API only.
451                 --
452                 -- (We need the source file to figure out the
453                 -- top-level environment, if we didn't compile this module
454                 -- from source then this field contains Nothing).
455                 --
456                 -- Strictly speaking this field should live in the
457                 -- HomeModInfo, but that leads to more plumbing.
458
459                 -- Instance declarations and rules
460         mi_insts     :: [IfaceInst],                    -- Sorted
461         mi_fam_insts :: [IfaceFamInst],                 -- Sorted
462         mi_rules     :: [IfaceRule],                    -- Sorted
463         mi_rule_vers :: !Version,       -- Version number for rules and 
464                                         -- instances (for classes and families)
465                                         -- combined
466
467                 -- Vectorisation information
468         mi_vect_info :: !IfaceVectInfo,
469
470                 -- Cached environments for easy lookup
471                 -- These are computed (lazily) from other fields
472                 -- and are not put into the interface file
473         mi_dep_fn  :: Name -> Maybe DeprecTxt,  -- Cached lookup for mi_deprecs
474         mi_fix_fn  :: OccName -> Fixity,        -- Cached lookup for mi_fixities
475         mi_ver_fn  :: OccName -> Maybe (OccName, Version)
476                         -- Cached lookup for mi_decls
477                         -- The Nothing in mi_ver_fn means that the thing
478                         -- isn't in decls. It's useful to know that when
479                         -- seeing if we are up to date wrt the old interface
480                         -- The 'OccName' is the parent of the name, if it has one.
481      }
482
483 -- Should be able to construct ModDetails from mi_decls in ModIface
484 data ModDetails
485    = ModDetails {
486         -- The next two fields are created by the typechecker
487         md_exports   :: [AvailInfo],
488         md_types     :: !TypeEnv,
489         md_insts     :: ![Instance],  -- Dfun-ids for the instances in this module
490         md_fam_insts :: ![FamInst],
491         md_rules     :: ![CoreRule],  -- Domain may include Ids from other modules
492         md_modBreaks :: !ModBreaks,   -- Breakpoint information for this module 
493         md_vect_info :: !VectInfo     -- Vectorisation information
494      }
495
496 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
497                                md_exports = [],
498                                md_insts     = [],
499                                md_rules     = [],
500                                md_fam_insts = [],
501                                md_modBreaks = emptyModBreaks,
502                                md_vect_info = noVectInfo
503                              } 
504
505 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
506 -- There is only one ModGuts at any time, the one for the module
507 -- being compiled right now.  Once it is compiled, a ModIface and 
508 -- ModDetails are extracted and the ModGuts is dicarded.
509
510 data ModGuts
511   = ModGuts {
512         mg_module    :: !Module,
513         mg_boot      :: IsBootInterface, -- Whether it's an hs-boot module
514         mg_exports   :: ![AvailInfo],    -- What it exports
515         mg_deps      :: !Dependencies,   -- What is below it, directly or
516                                          --   otherwise 
517         mg_dir_imps  :: ![Module],       -- Directly-imported modules; used to
518                                          --     generate initialisation code
519         mg_usages    :: ![Usage],        -- Version info for what it needed
520
521         mg_rdr_env   :: !GlobalRdrEnv,   -- Top-level lexical environment
522         mg_fix_env   :: !FixityEnv,      -- Fixity env, for things declared in
523                                          --   this module 
524
525         mg_fam_inst_env :: FamInstEnv,   -- Type-family instance enviroment
526                                          -- for *home-package* modules (including
527                                          -- this one).  c.f. tcg_fam_inst_env
528
529         mg_types     :: !TypeEnv,
530         mg_insts     :: ![Instance],     -- Instances 
531         mg_fam_insts :: ![FamInst],      -- Instances 
532         mg_rules     :: ![CoreRule],     -- Rules from this module
533         mg_binds     :: ![CoreBind],     -- Bindings for this module
534         mg_foreign   :: !ForeignStubs,
535         mg_deprecs   :: !Deprecations,   -- Deprecations declared in the module
536         mg_hpc_info  :: !HpcInfo,        -- info about coverage tick boxes
537         mg_modBreaks :: !ModBreaks,
538         mg_vect_info :: !VectInfo        -- Pool of vectorised declarations
539     }
540
541 -- The ModGuts takes on several slightly different forms:
542 --
543 -- After simplification, the following fields change slightly:
544 --      mg_rules        Orphan rules only (local ones now attached to binds)
545 --      mg_binds        With rules attached
546
547
548 ---------------------------------------------------------
549 -- The Tidy pass forks the information about this module: 
550 --      * one lot goes to interface file generation (ModIface)
551 --        and later compilations (ModDetails)
552 --      * the other lot goes to code generation (CgGuts)
553 data CgGuts 
554   = CgGuts {
555         cg_module   :: !Module,
556
557         cg_tycons   :: [TyCon],
558                 -- Algebraic data types (including ones that started
559                 -- life as classes); generate constructors and info
560                 -- tables Includes newtypes, just for the benefit of
561                 -- External Core
562
563         cg_binds    :: [CoreBind],
564                 -- The tidied main bindings, including
565                 -- previously-implicit bindings for record and class
566                 -- selectors, and data construtor wrappers.  But *not*
567                 -- data constructor workers; reason: we we regard them
568                 -- as part of the code-gen of tycons
569
570         cg_dir_imps :: ![Module],
571                 -- Directly-imported modules; used to generate
572                 -- initialisation code
573
574         cg_foreign  :: !ForeignStubs,   
575         cg_dep_pkgs :: ![PackageId],    -- Used to generate #includes for C code gen
576         cg_hpc_info :: !HpcInfo         -- info about coverage tick boxes
577     }
578
579 -----------------------------------
580 data ModImports
581   = ModImports {
582         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
583                                                 -- Boolean is true if we imported the whole
584                                                 --      module (apart, perhaps, from hiding some)
585         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
586                                                 --      directly or indirectly
587         imp_home_names :: !NameSet              -- Home package things on which we depend,
588                                                 --      directly or indirectly
589     }
590
591 -----------------------------------
592 data ForeignStubs = NoStubs
593                   | ForeignStubs
594                         SDoc            -- Header file prototypes for
595                                         --      "foreign exported" functions
596                         SDoc            -- C stubs to use when calling
597                                         --      "foreign exported" functions
598                         [FastString]    -- Headers that need to be included
599                                         --      into C code generated for this module
600                         [Id]            -- Foreign-exported binders
601                                         --      we have to generate code to register these
602
603 \end{code}
604
605 \begin{code}
606 emptyModIface :: Module -> ModIface
607 emptyModIface mod
608   = ModIface { mi_module   = mod,
609                mi_mod_vers = initialVersion,
610                mi_orphan   = False,
611                mi_finsts   = False,
612                mi_boot     = False,
613                mi_deps     = noDependencies,
614                mi_usages   = [],
615                mi_exports  = [],
616                mi_exp_vers = initialVersion,
617                mi_fixities = [],
618                mi_deprecs  = NoDeprecs,
619                mi_insts     = [],
620                mi_fam_insts = [],
621                mi_rules     = [],
622                mi_decls     = [],
623                mi_globals   = Nothing,
624                mi_rule_vers = initialVersion,
625                mi_vect_info = noIfaceVectInfo,
626                mi_dep_fn = emptyIfaceDepCache,
627                mi_fix_fn = emptyIfaceFixCache,
628                mi_ver_fn = emptyIfaceVerCache
629     }           
630 \end{code}
631
632
633 %************************************************************************
634 %*                                                                      *
635 \subsection{The interactive context}
636 %*                                                                      *
637 %************************************************************************
638
639 \begin{code}
640 data InteractiveContext 
641   = InteractiveContext { 
642         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
643                                         -- these modules
644
645         ic_exports :: [Module],         -- Include just the exports of these
646                                         -- modules
647
648         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
649                                         -- ic_toplev_scope and ic_exports
650
651         ic_tmp_ids :: [Id],             -- Names bound during interaction.
652                                         -- Later Ids shadow
653                                         -- earlier ones with the same OccName.
654
655         ic_tyvars :: TyVarSet           -- skolem type variables free in
656                                         -- ic_tmp_ids.  These arise at
657                                         -- breakpoints in a polymorphic 
658                                         -- context, where we have only partial
659                                         -- type information.
660
661 #ifdef GHCI
662         , ic_resume :: [Resume]         -- the stack of breakpoint contexts
663 #endif
664     }
665
666
667 emptyInteractiveContext
668   = InteractiveContext { ic_toplev_scope = [],
669                          ic_exports = [],
670                          ic_rn_gbl_env = emptyGlobalRdrEnv,
671                          ic_tmp_ids = [],
672                          ic_tyvars = emptyVarSet
673 #ifdef GHCI
674                          , ic_resume = []
675 #endif
676                        }
677
678 icPrintUnqual :: InteractiveContext -> PrintUnqualified
679 icPrintUnqual ictxt = mkPrintUnqualified (ic_rn_gbl_env ictxt)
680
681
682 extendInteractiveContext
683         :: InteractiveContext
684         -> [Id]
685         -> TyVarSet
686         -> InteractiveContext
687 extendInteractiveContext ictxt ids tyvars
688   = ictxt { ic_tmp_ids =  ic_tmp_ids ictxt ++ ids,
689                           -- NB. must be this way around, because we want
690                           -- new ids to shadow existing bindings.
691             ic_tyvars   = ic_tyvars ictxt `unionVarSet` tyvars }
692 \end{code}
693
694 %************************************************************************
695 %*                                                                      *
696         Building a PrintUnqualified             
697 %*                                                                      *
698 %************************************************************************
699
700 \begin{code}
701 mkPrintUnqualified :: GlobalRdrEnv -> PrintUnqualified
702 mkPrintUnqualified env = (qual_name, qual_mod)
703   where
704   qual_name mod occ
705         | null gres = Just (moduleName mod)
706                 -- it isn't in scope at all, this probably shouldn't happen,
707                 -- but we'll qualify it by the original module anyway.
708         | any unQualOK gres = Nothing
709         | (Imported is : _) <- map gre_prov gres, (idecl : _) <- is
710           = Just (is_as (is_decl idecl))
711         | otherwise = panic "mkPrintUnqualified" 
712       where
713         gres  = [ gre | gre <- lookupGlobalRdrEnv env occ,
714                         nameModule (gre_name gre) == mod ]
715
716   qual_mod mod = Nothing       -- For now...
717 \end{code}
718
719
720 %************************************************************************
721 %*                                                                      *
722                 TyThing
723 %*                                                                      *
724 %************************************************************************
725
726 \begin{code}
727 implicitTyThings :: TyThing -> [TyThing]
728 -- If you change this, make sure you change LoadIface.ifaceDeclSubBndrs in sync
729
730 implicitTyThings (AnId id)   = []
731
732         -- For type constructors, add the data cons (and their extras),
733         -- and the selectors and generic-programming Ids too
734         --
735         -- Newtypes don't have a worker Id, so don't generate that?
736 implicitTyThings (ATyCon tc) = implicitCoTyCon tc ++
737                                map AnId (tyConSelIds tc) ++ 
738                                concatMap (extras_plus . ADataCon) 
739                                          (tyConDataCons tc)
740                      
741         -- For classes, add the class selector Ids, and assoicated TyCons
742         -- and the class TyCon too (and its extras)
743 implicitTyThings (AClass cl) 
744   = map AnId (classSelIds cl) ++
745     map ATyCon (classATs cl) ++
746         -- No extras_plus for the classATs, because they
747         -- are only the family decls; they have no implicit things
748     extras_plus (ATyCon (classTyCon cl))
749
750         -- For data cons add the worker and wrapper (if any)
751 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
752
753 -- | returns 'True' if there should be no interface-file declaration
754 -- for this thing on its own: either it is built-in, or it is part
755 -- of some other declaration, or it is generated implicitly by some
756 -- other declaration.
757 isImplicitTyThing :: TyThing -> Bool
758 isImplicitTyThing (ADataCon _)  = True
759 isImplicitTyThing (AnId     id) = isImplicitId id
760 isImplicitTyThing (AClass   _)  = False
761 isImplicitTyThing (ATyCon   tc) = isImplicitTyCon tc
762
763         -- For newtypes and indexed data types, add the implicit coercion tycon
764 implicitCoTyCon tc 
765   = map ATyCon . catMaybes $ [newTyConCo_maybe tc, 
766                               tyConFamilyCoercion_maybe tc]
767
768 extras_plus thing = thing : implicitTyThings thing
769
770 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
771 extendTypeEnvWithIds env ids
772   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
773 \end{code}
774
775 %************************************************************************
776 %*                                                                      *
777                 TypeEnv
778 %*                                                                      *
779 %************************************************************************
780
781 \begin{code}
782 type TypeEnv = NameEnv TyThing
783
784 emptyTypeEnv    :: TypeEnv
785 typeEnvElts     :: TypeEnv -> [TyThing]
786 typeEnvClasses  :: TypeEnv -> [Class]
787 typeEnvTyCons   :: TypeEnv -> [TyCon]
788 typeEnvIds      :: TypeEnv -> [Id]
789 typeEnvDataCons :: TypeEnv -> [DataCon]
790 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
791
792 emptyTypeEnv        = emptyNameEnv
793 typeEnvElts     env = nameEnvElts env
794 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
795 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
796 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
797 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
798
799 mkTypeEnv :: [TyThing] -> TypeEnv
800 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
801                 
802 lookupTypeEnv = lookupNameEnv
803
804 -- Extend the type environment
805 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
806 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
807
808 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
809 extendTypeEnvList env things = foldl extendTypeEnv env things
810 \end{code}
811
812 \begin{code}
813 lookupType :: DynFlags
814            -> HomePackageTable
815            -> PackageTypeEnv
816            -> Name
817            -> Maybe TyThing
818
819 lookupType dflags hpt pte name
820   -- in one-shot, we don't use the HPT
821   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
822   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
823        lookupNameEnv (md_types (hm_details hm)) name
824   | otherwise
825   = lookupNameEnv pte name
826   where mod = nameModule name
827         this_pkg = thisPackage dflags
828 \end{code}
829
830 \begin{code}
831 tyThingTyCon (ATyCon tc) = tc
832 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
833
834 tyThingClass (AClass cls) = cls
835 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
836
837 tyThingDataCon (ADataCon dc) = dc
838 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
839
840 tyThingId (AnId id) = id
841 tyThingId other     = pprPanic "tyThingId" (ppr other)
842 \end{code}
843
844 %************************************************************************
845 %*                                                                      *
846 \subsection{Auxiliary types}
847 %*                                                                      *
848 %************************************************************************
849
850 These types are defined here because they are mentioned in ModDetails,
851 but they are mostly elaborated elsewhere
852
853 \begin{code}
854 mkIfaceVerCache :: [(Version,IfaceDecl)]
855                 -> (OccName -> Maybe (OccName, Version))
856 mkIfaceVerCache pairs 
857   = \occ -> lookupOccEnv env occ
858   where
859     env = foldr add_decl emptyOccEnv pairs
860     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
861       where
862           decl_name = ifName d
863           env1 = extendOccEnv env0 decl_name (decl_name, v)
864           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
865
866 emptyIfaceVerCache :: OccName -> Maybe (OccName, Version)
867 emptyIfaceVerCache occ = Nothing
868
869 ------------------ Deprecations -------------------------
870 data Deprecs a
871   = NoDeprecs
872   | DeprecAll DeprecTxt -- Whole module deprecated
873   | DeprecSome a        -- Some specific things deprecated
874   deriving( Eq )
875
876 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
877 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
878         -- Keep the OccName so we can flatten the NameEnv to
879         -- get an IfaceDeprecs from a Deprecations
880         -- Only an OccName is needed, because a deprecation always
881         -- applies to things defined in the module in which the
882         -- deprecation appears.
883
884 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
885 mkIfaceDepCache NoDeprecs         = \n -> Nothing
886 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
887 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
888
889 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
890 emptyIfaceDepCache n = Nothing
891
892 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
893 plusDeprecs d NoDeprecs = d
894 plusDeprecs NoDeprecs d = d
895 plusDeprecs d (DeprecAll t) = DeprecAll t
896 plusDeprecs (DeprecAll t) d = DeprecAll t
897 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
898 \end{code}
899
900
901 \begin{code}
902 type Avails       = [AvailInfo]
903 type AvailInfo    = GenAvailInfo Name
904 type RdrAvailInfo = GenAvailInfo OccName
905
906 data GenAvailInfo name  = Avail name     -- An ordinary identifier
907                         | AvailTC name   -- The name of the type or class
908                                   [name] -- The available pieces of type/class.
909                                          -- NB: If the type or class is itself
910                                          -- to be in scope, it must be in this list.
911                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
912                         deriving( Eq )
913                         -- Equality used when deciding if the interface has changed
914
915 type IfaceExport = (Module, [GenAvailInfo OccName])
916
917 availsToNameSet :: [AvailInfo] -> NameSet
918 availsToNameSet avails = foldr add emptyNameSet avails
919       where add avail set = addListToNameSet set (availNames avail)
920
921 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
922 availsToNameEnv avails = foldr add emptyNameEnv avails
923      where add avail env = extendNameEnvList env
924                                 (zip (availNames avail) (repeat avail))
925
926 availName :: GenAvailInfo name -> name
927 availName (Avail n)     = n
928 availName (AvailTC n _) = n
929
930 availNames :: GenAvailInfo name -> [name]
931 availNames (Avail n)      = [n]
932 availNames (AvailTC n ns) = ns
933
934 instance Outputable n => Outputable (GenAvailInfo n) where
935    ppr = pprAvail
936
937 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
938 pprAvail (Avail n)      = ppr n
939 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
940 \end{code}
941
942 \begin{code}
943 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
944 mkIfaceFixCache pairs 
945   = \n -> lookupOccEnv env n `orElse` defaultFixity
946   where
947    env = mkOccEnv pairs
948
949 emptyIfaceFixCache :: OccName -> Fixity
950 emptyIfaceFixCache n = defaultFixity
951
952 -- This fixity environment is for source code only
953 type FixityEnv = NameEnv FixItem
954
955 -- We keep the OccName in the range so that we can generate an interface from it
956 data FixItem = FixItem OccName Fixity SrcSpan
957
958 instance Outputable FixItem where
959   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
960
961 emptyFixityEnv :: FixityEnv
962 emptyFixityEnv = emptyNameEnv
963
964 lookupFixity :: FixityEnv -> Name -> Fixity
965 lookupFixity env n = case lookupNameEnv env n of
966                         Just (FixItem _ fix _) -> fix
967                         Nothing                -> defaultFixity
968 \end{code}
969
970
971 %************************************************************************
972 %*                                                                      *
973 \subsection{WhatsImported}
974 %*                                                                      *
975 %************************************************************************
976
977 \begin{code}
978 type WhetherHasOrphans   = Bool
979         -- An "orphan" is 
980         --      * an instance decl in a module other than the defn module for 
981         --              one of the tycons or classes in the instance head
982         --      * a transformation rule in a module other than the one defining
983         --              the function in the head of the rule.
984
985 type WhetherHasFamInst = Bool        -- This module defines family instances?
986
987 type IsBootInterface = Bool
988
989 -- Dependency info about modules and packages below this one
990 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
991 -- The orphan modules in `dep_orphs' do *not* include family instance orphans,
992 -- as they are anyway included in `dep_finsts'.
993 --
994 -- Invariant: the dependencies of a module M never includes M
995 -- Invariant: the lists are unordered, with no duplicates
996 data Dependencies
997   = Deps { dep_mods   :: [(ModuleName,      -- Home-package module dependencies
998                            IsBootInterface)]
999          , dep_pkgs   :: [PackageId]        -- External package dependencies
1000          , dep_orphs  :: [Module]           -- Orphan modules (whether home or
1001                                             -- external pkg)
1002          , dep_finsts :: [Module]           -- Modules that contain family
1003                                             -- instances (whether home or
1004                                             -- external pkg)
1005          }
1006   deriving( Eq )
1007         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1008
1009 noDependencies :: Dependencies
1010 noDependencies = Deps [] [] [] []
1011           
1012 data Usage
1013   = Usage { usg_name     :: ModuleName,                 -- Name of the module
1014             usg_mod      :: Version,                    -- Module version
1015             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
1016                 -- NB. usages are for parent names only, eg. tycon but not constructors.
1017             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
1018             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
1019                                                         -- modules this will always be initialVersion)
1020     }       deriving( Eq )
1021         -- This type doesn't let you say "I imported f but none of the rules in
1022         -- the module". If you use anything in the module you get its rule version
1023         -- So if the rules change, you'll recompile, even if you don't use them.
1024         -- This is easy to implement, and it's safer: you might not have used the rules last
1025         -- time round, but if someone has added a new rule you might need it this time
1026
1027         -- The export list field is (Just v) if we depend on the export list:
1028         --      i.e. we imported the module directly, whether or not we
1029         --           enumerated the things we imported, or just imported everything
1030         -- We need to recompile if M's exports change, because 
1031         -- if the import was    import M,       we might now have a name clash in the 
1032         --                                      importing module.
1033         -- if the import was    import M(x)     M might no longer export x
1034         -- The only way we don't depend on the export list is if we have
1035         --                      import M()
1036         -- And of course, for modules that aren't imported directly we don't
1037         -- depend on their export lists
1038 \end{code}
1039
1040
1041 %************************************************************************
1042 %*                                                                      *
1043                 The External Package State
1044 %*                                                                      *
1045 %************************************************************************
1046
1047 \begin{code}
1048 type PackageTypeEnv    = TypeEnv
1049 type PackageRuleBase   = RuleBase
1050 type PackageInstEnv    = InstEnv
1051 type PackageFamInstEnv = FamInstEnv
1052 type PackageVectInfo   = VectInfo
1053
1054 data ExternalPackageState
1055   = EPS {
1056         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1057                 -- In OneShot mode (only), home-package modules
1058                 -- accumulate in the external package state, and are
1059                 -- sucked in lazily.  For these home-pkg modules
1060                 -- (only) we need to record which are boot modules.
1061                 -- We set this field after loading all the
1062                 -- explicitly-imported interfaces, but before doing
1063                 -- anything else
1064                 --
1065                 -- The ModuleName part is not necessary, but it's useful for
1066                 -- debug prints, and it's convenient because this field comes
1067                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
1068
1069         eps_PIT :: !PackageIfaceTable,
1070                 -- The ModuleIFaces for modules in external packages
1071                 -- whose interfaces we have opened
1072                 -- The declarations in these interface files are held in
1073                 -- eps_decls, eps_inst_env, eps_fam_inst_env, eps_rules
1074                 -- (below), not in the mi_decls fields of the iPIT.  
1075                 -- What _is_ in the iPIT is:
1076                 --      * The Module 
1077                 --      * Version info
1078                 --      * Its exports
1079                 --      * Fixities
1080                 --      * Deprecations
1081
1082         eps_PTE :: !PackageTypeEnv,        -- Domain = external-package modules
1083
1084         eps_inst_env     :: !PackageInstEnv,   -- The total InstEnv accumulated
1085                                                -- from all the external-package
1086                                                -- modules 
1087         eps_fam_inst_env :: !PackageFamInstEnv,-- Ditto FamInstEnv
1088         eps_rule_base    :: !PackageRuleBase,  -- Ditto RuleEnv
1089         eps_vect_info    :: !PackageVectInfo,  -- Ditto VectInfo
1090
1091         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- identifies family
1092                                                        -- instances of each mod 
1093         eps_stats :: !EpsStats
1094   }
1095
1096 -- "In" means read from iface files
1097 -- "Out" means actually sucked in and type-checked
1098 data EpsStats = EpsStats { n_ifaces_in
1099                          , n_decls_in, n_decls_out 
1100                          , n_rules_in, n_rules_out
1101                          , n_insts_in, n_insts_out :: !Int }
1102
1103 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1104 -- Add stats for one newly-read interface
1105 addEpsInStats stats n_decls n_insts n_rules
1106   = stats { n_ifaces_in = n_ifaces_in stats + 1
1107           , n_decls_in  = n_decls_in stats + n_decls
1108           , n_insts_in  = n_insts_in stats + n_insts
1109           , n_rules_in  = n_rules_in stats + n_rules }
1110 \end{code}
1111
1112 The NameCache makes sure that there is just one Unique assigned for
1113 each original name; i.e. (module-name, occ-name) pair.  The Name is
1114 always stored as a Global, and has the SrcLoc of its binding location.
1115 Actually that's not quite right.  When we first encounter the original
1116 name, we might not be at its binding site (e.g. we are reading an
1117 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1118 its binding site, we fix it up.
1119
1120 \begin{code}
1121 data NameCache
1122  = NameCache {  nsUniqs :: UniqSupply,
1123                 -- Supply of uniques
1124                 nsNames :: OrigNameCache,
1125                 -- Ensures that one original name gets one unique
1126                 nsIPs   :: OrigIParamCache
1127                 -- Ensures that one implicit parameter name gets one unique
1128    }
1129
1130 type OrigNameCache   = ModuleEnv (OccEnv Name)
1131 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
1132 \end{code}
1133
1134
1135
1136 %************************************************************************
1137 %*                                                                      *
1138                 The module graph and ModSummary type
1139         A ModSummary is a node in the compilation manager's
1140         dependency graph, and it's also passed to hscMain
1141 %*                                                                      *
1142 %************************************************************************
1143
1144 A ModuleGraph contains all the nodes from the home package (only).  
1145 There will be a node for each source module, plus a node for each hi-boot
1146 module.
1147
1148 \begin{code}
1149 type ModuleGraph = [ModSummary]  -- The module graph, 
1150                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
1151
1152 emptyMG :: ModuleGraph
1153 emptyMG = []
1154
1155 -- The nodes of the module graph are
1156 --      EITHER a regular Haskell source module
1157 --      OR     a hi-boot source module
1158
1159 data ModSummary
1160    = ModSummary {
1161         ms_mod       :: Module,                 -- Identity of the module
1162         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
1163         ms_location  :: ModLocation,            -- Location
1164         ms_hs_date   :: ClockTime,              -- Timestamp of source file
1165         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
1166         ms_srcimps   :: [Located ModuleName],   -- Source imports
1167         ms_imps      :: [Located ModuleName],   -- Non-source imports
1168         ms_hspp_file :: FilePath,               -- Filename of preprocessed source.
1169         ms_hspp_opts :: DynFlags,               -- Cached flags from OPTIONS, INCLUDE
1170                                                 -- and LANGUAGE pragmas.
1171         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
1172      }
1173
1174 ms_mod_name :: ModSummary -> ModuleName
1175 ms_mod_name = moduleName . ms_mod
1176
1177 -- The ModLocation contains both the original source filename and the
1178 -- filename of the cleaned-up source file after all preprocessing has been
1179 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1180 -- all files anyway, and there's no point in doing this twice -- just 
1181 -- park the result in a temp file, put the name of it in the location,
1182 -- and let @compile@ read from that file on the way back up.
1183
1184 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1185 -- the ms_hs_date and imports can, of course, change
1186
1187 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1188 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1189 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1190 msObjFilePath ms = ml_obj_file (ms_location ms)
1191
1192 isBootSummary :: ModSummary -> Bool
1193 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1194
1195 instance Outputable ModSummary where
1196    ppr ms
1197       = sep [text "ModSummary {",
1198              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1199                           text "ms_mod =" <+> ppr (ms_mod ms) 
1200                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1201                           text "ms_imps =" <+> ppr (ms_imps ms),
1202                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1203              char '}'
1204             ]
1205
1206 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1207 showModMsg target recomp mod_summary
1208   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1209                     char '(', text (msHsFilePath mod_summary) <> comma,
1210                     case target of
1211                       HscInterpreted | recomp 
1212                                  -> text "interpreted"
1213                       HscNothing -> text "nothing"
1214                       _other     -> text (msObjFilePath mod_summary),
1215                     char ')'])
1216  where 
1217     mod     = moduleName (ms_mod mod_summary)
1218     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1219 \end{code}
1220
1221
1222 %************************************************************************
1223 %*                                                                      *
1224 \subsection{Hpc Support}
1225 %*                                                                      *
1226 %************************************************************************
1227
1228 \begin{code}
1229 data HpcInfo = HpcInfo 
1230      { hpcInfoTickCount :: Int 
1231      , hpcInfoHash      :: Int  
1232      }
1233      | NoHpcInfo
1234
1235 noHpcInfo :: HpcInfo
1236 noHpcInfo = NoHpcInfo
1237 \end{code}
1238
1239 %************************************************************************
1240 %*                                                                      *
1241 \subsection{Vectorisation Support}
1242 %*                                                                      *
1243 %************************************************************************
1244
1245 The following information is generated and consumed by the vectorisation
1246 subsystem.  It communicates the vectorisation status of declarations from one
1247 module to another.
1248
1249 Why do we need both f and f_CC in the ModGuts/ModDetails/EPS version VectInfo
1250 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1251 closure conversion, we need to know `f_CC', whose `Var' we cannot lookup based
1252 on just the OccName easily in a Core pass.
1253
1254 \begin{code}
1255 -- ModGuts/ModDetails/EPS version
1256 data VectInfo      
1257   = VectInfo {
1258       vectInfoCCVar :: VarEnv (Var, Var)        -- (f, f_CC) keyed on f
1259                                                 -- always tidy, even in ModGuts
1260     }
1261
1262 -- ModIface version
1263 data IfaceVectInfo 
1264   = IfaceVectInfo {
1265       ifaceVectInfoCCVar :: [Name]              -- all variables in here have
1266                                                 -- a closure-converted variant
1267                                                 -- the name of the CC'ed variant
1268                                                 -- is determined by `mkCloOcc'
1269     }
1270
1271 noVectInfo :: VectInfo
1272 noVectInfo = VectInfo emptyVarEnv
1273
1274 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1275 plusVectInfo vi1 vi2 = 
1276   VectInfo (vectInfoCCVar vi1 `plusVarEnv` vectInfoCCVar vi2)
1277
1278 noIfaceVectInfo :: IfaceVectInfo
1279 noIfaceVectInfo = IfaceVectInfo []
1280 \end{code}
1281
1282 %************************************************************************
1283 %*                                                                      *
1284 \subsection{Linkable stuff}
1285 %*                                                                      *
1286 %************************************************************************
1287
1288 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1289 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1290
1291 \begin{code}
1292 data Linkable = LM {
1293   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1294                                         -- (i.e. when the bytecodes were produced,
1295                                         --       or the mod date on the files)
1296   linkableModule   :: Module,           -- Should be Module, but see below
1297   linkableUnlinked :: [Unlinked]
1298  }
1299
1300 isObjectLinkable :: Linkable -> Bool
1301 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1302   where unlinked = linkableUnlinked l
1303         -- A linkable with no Unlinked's is treated as a BCO.  We can
1304         -- generate a linkable with no Unlinked's as a result of
1305         -- compiling a module in HscNothing mode, and this choice
1306         -- happens to work well with checkStability in module GHC.
1307
1308 instance Outputable Linkable where
1309    ppr (LM when_made mod unlinkeds)
1310       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1311         $$ nest 3 (ppr unlinkeds)
1312
1313 -------------------------------------------
1314 data Unlinked
1315    = DotO FilePath
1316    | DotA FilePath
1317    | DotDLL FilePath
1318    | BCOs CompiledByteCode
1319
1320 #ifndef GHCI
1321 data CompiledByteCode = NoByteCode
1322 #endif
1323
1324 instance Outputable Unlinked where
1325    ppr (DotO path)   = text "DotO" <+> text path
1326    ppr (DotA path)   = text "DotA" <+> text path
1327    ppr (DotDLL path) = text "DotDLL" <+> text path
1328 #ifdef GHCI
1329    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1330 #else
1331    ppr (BCOs bcos)   = text "No byte code"
1332 #endif
1333
1334 isObject (DotO _)   = True
1335 isObject (DotA _)   = True
1336 isObject (DotDLL _) = True
1337 isObject _          = False
1338
1339 isInterpretable = not . isObject
1340
1341 nameOfObject (DotO fn)   = fn
1342 nameOfObject (DotA fn)   = fn
1343 nameOfObject (DotDLL fn) = fn
1344 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1345
1346 byteCodeOfObject (BCOs bc) = bc
1347 byteCodeOfObject other     = pprPanic "byteCodeOfObject" (ppr other)
1348 \end{code}
1349
1350 %************************************************************************
1351 %*                                                                      *
1352 \subsection{Breakpoint Support}
1353 %*                                                                      *
1354 %************************************************************************
1355
1356 \begin{code}
1357 type BreakIndex = Int
1358
1359 -- | all the information about the breakpoints for a given module
1360 data ModBreaks
1361    = ModBreaks
1362    { modBreaks_flags :: BreakArray
1363         -- The array of flags, one per breakpoint, 
1364         -- indicating which breakpoints are enabled.
1365    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
1366         -- An array giving the source span of each breakpoint.
1367    , modBreaks_vars :: !(Array BreakIndex [OccName])
1368         -- An array giving the names of the free variables at each breakpoint.
1369    }
1370
1371 emptyModBreaks :: ModBreaks
1372 emptyModBreaks = ModBreaks
1373    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
1374          -- Todo: can we avoid this? 
1375    , modBreaks_locs = array (0,-1) []
1376    , modBreaks_vars = array (0,-1) []
1377    }
1378 \end{code}