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