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