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