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