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