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