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