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