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