Improve name-printing on unification mis-matches, when types share a common occurrenc...
[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_fam_inst_env :: FamInstEnv,   -- Type-family instance enviroment
525                                          -- for *home-package* modules (including
526                                          -- this one).  c.f. tcg_fam_inst_env
527
528         mg_types     :: !TypeEnv,
529         mg_insts     :: ![Instance],     -- Instances 
530         mg_fam_insts :: ![FamInst],      -- Instances 
531         mg_rules     :: ![CoreRule],     -- Rules from this module
532         mg_binds     :: ![CoreBind],     -- Bindings for this module
533         mg_foreign   :: !ForeignStubs,
534         mg_deprecs   :: !Deprecations,   -- Deprecations declared in the module
535         mg_hpc_info  :: !HpcInfo,        -- info about coverage tick boxes
536         mg_modBreaks :: !ModBreaks,
537         mg_vect_info :: !VectInfo        -- Pool of vectorised declarations
538     }
539
540 -- The ModGuts takes on several slightly different forms:
541 --
542 -- After simplification, the following fields change slightly:
543 --      mg_rules        Orphan rules only (local ones now attached to binds)
544 --      mg_binds        With rules attached
545
546
547 ---------------------------------------------------------
548 -- The Tidy pass forks the information about this module: 
549 --      * one lot goes to interface file generation (ModIface)
550 --        and later compilations (ModDetails)
551 --      * the other lot goes to code generation (CgGuts)
552 data CgGuts 
553   = CgGuts {
554         cg_module   :: !Module,
555
556         cg_tycons   :: [TyCon],
557                 -- Algebraic data types (including ones that started
558                 -- life as classes); generate constructors and info
559                 -- tables Includes newtypes, just for the benefit of
560                 -- External Core
561
562         cg_binds    :: [CoreBind],
563                 -- The tidied main bindings, including
564                 -- previously-implicit bindings for record and class
565                 -- selectors, and data construtor wrappers.  But *not*
566                 -- data constructor workers; reason: we we regard them
567                 -- as part of the code-gen of tycons
568
569         cg_dir_imps :: ![Module],
570                 -- Directly-imported modules; used to generate
571                 -- initialisation code
572
573         cg_foreign  :: !ForeignStubs,   
574         cg_dep_pkgs :: ![PackageId],    -- Used to generate #includes for C code gen
575         cg_hpc_info :: !HpcInfo         -- info about coverage tick boxes
576     }
577
578 -----------------------------------
579 data ModImports
580   = ModImports {
581         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
582                                                 -- Boolean is true if we imported the whole
583                                                 --      module (apart, perhaps, from hiding some)
584         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
585                                                 --      directly or indirectly
586         imp_home_names :: !NameSet              -- Home package things on which we depend,
587                                                 --      directly or indirectly
588     }
589
590 -----------------------------------
591 data ForeignStubs = NoStubs
592                   | ForeignStubs
593                         SDoc            -- Header file prototypes for
594                                         --      "foreign exported" functions
595                         SDoc            -- C stubs to use when calling
596                                         --      "foreign exported" functions
597                         [FastString]    -- Headers that need to be included
598                                         --      into C code generated for this module
599                         [Id]            -- Foreign-exported binders
600                                         --      we have to generate code to register these
601
602 \end{code}
603
604 \begin{code}
605 emptyModIface :: Module -> ModIface
606 emptyModIface mod
607   = ModIface { mi_module   = mod,
608                mi_mod_vers = initialVersion,
609                mi_orphan   = False,
610                mi_finsts   = False,
611                mi_boot     = False,
612                mi_deps     = noDependencies,
613                mi_usages   = [],
614                mi_exports  = [],
615                mi_exp_vers = initialVersion,
616                mi_fixities = [],
617                mi_deprecs  = NoDeprecs,
618                mi_insts     = [],
619                mi_fam_insts = [],
620                mi_rules     = [],
621                mi_decls     = [],
622                mi_globals   = Nothing,
623                mi_rule_vers = initialVersion,
624                mi_vect_info = noIfaceVectInfo,
625                mi_dep_fn = emptyIfaceDepCache,
626                mi_fix_fn = emptyIfaceFixCache,
627                mi_ver_fn = emptyIfaceVerCache
628     }           
629 \end{code}
630
631
632 %************************************************************************
633 %*                                                                      *
634 \subsection{The interactive context}
635 %*                                                                      *
636 %************************************************************************
637
638 \begin{code}
639 data InteractiveContext 
640   = InteractiveContext { 
641         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
642                                         -- these modules
643
644         ic_exports :: [Module],         -- Include just the exports of these
645                                         -- modules
646
647         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
648                                         -- ic_toplev_scope and ic_exports
649
650         ic_tmp_ids :: [Id],             -- Names bound during interaction.
651                                         -- Later Ids shadow
652                                         -- earlier ones with the same OccName.
653
654         ic_tyvars :: TyVarSet           -- skolem type variables free in
655                                         -- ic_tmp_ids.  These arise at
656                                         -- breakpoints in a polymorphic 
657                                         -- context, where we have only partial
658                                         -- type information.
659
660 #ifdef GHCI
661         , ic_resume :: [Resume]         -- the stack of breakpoint contexts
662 #endif
663     }
664
665
666 emptyInteractiveContext
667   = InteractiveContext { ic_toplev_scope = [],
668                          ic_exports = [],
669                          ic_rn_gbl_env = emptyGlobalRdrEnv,
670                          ic_tmp_ids = [],
671                          ic_tyvars = emptyVarSet
672 #ifdef GHCI
673                          , ic_resume = []
674 #endif
675                        }
676
677 icPrintUnqual :: InteractiveContext -> PrintUnqualified
678 icPrintUnqual ictxt = mkPrintUnqualified (ic_rn_gbl_env ictxt)
679
680
681 extendInteractiveContext
682         :: InteractiveContext
683         -> [Id]
684         -> TyVarSet
685         -> InteractiveContext
686 extendInteractiveContext ictxt ids tyvars
687   = ictxt { ic_tmp_ids =  ic_tmp_ids ictxt ++ ids,
688                           -- NB. must be this way around, because we want
689                           -- new ids to shadow existing bindings.
690             ic_tyvars   = ic_tyvars ictxt `unionVarSet` tyvars }
691 \end{code}
692
693 %************************************************************************
694 %*                                                                      *
695         Building a PrintUnqualified             
696 %*                                                                      *
697 %************************************************************************
698
699 \begin{code}
700 mkPrintUnqualified :: GlobalRdrEnv -> PrintUnqualified
701 mkPrintUnqualified env = (qual_name, qual_mod)
702   where
703   qual_name mod occ     -- The (mod,occ) pair is the original name of the thing
704         | [gre] <- unqual_gres, right_name gre = Nothing
705                 -- If there's a unique entity that's in scope unqualified with 'occ'
706                 -- AND that entity is the right one, then we can use the unqualified name
707
708         | [gre] <- qual_gres = Just (get_qual_mod (gre_prov gre))
709
710         | null qual_gres = Just (moduleName mod)
711                 -- it isn't in scope at all, this probably shouldn't happen,
712                 -- but we'll qualify it by the original module anyway.
713
714         | otherwise = panic "mkPrintUnqualified"
715       where
716         right_name gre = nameModule (gre_name gre) == mod
717
718         unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
719         qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
720
721         get_qual_mod LocalDef      = moduleName mod
722         get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
723
724   qual_mod mod = Nothing       -- For now, we never qualify module names with their packages
725 \end{code}
726
727
728 %************************************************************************
729 %*                                                                      *
730                 TyThing
731 %*                                                                      *
732 %************************************************************************
733
734 \begin{code}
735 implicitTyThings :: TyThing -> [TyThing]
736 -- If you change this, make sure you change LoadIface.ifaceDeclSubBndrs in sync
737
738 implicitTyThings (AnId id)   = []
739
740         -- For type constructors, add the data cons (and their extras),
741         -- and the selectors and generic-programming Ids too
742         --
743         -- Newtypes don't have a worker Id, so don't generate that?
744 implicitTyThings (ATyCon tc) = implicitCoTyCon tc ++
745                                map AnId (tyConSelIds tc) ++ 
746                                concatMap (extras_plus . ADataCon) 
747                                          (tyConDataCons tc)
748                      
749         -- For classes, add the class selector Ids, and assoicated TyCons
750         -- and the class TyCon too (and its extras)
751 implicitTyThings (AClass cl) 
752   = map AnId (classSelIds cl) ++
753     map ATyCon (classATs cl) ++
754         -- No extras_plus for the classATs, because they
755         -- are only the family decls; they have no implicit things
756     extras_plus (ATyCon (classTyCon cl))
757
758         -- For data cons add the worker and wrapper (if any)
759 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
760
761 -- | returns 'True' if there should be no interface-file declaration
762 -- for this thing on its own: either it is built-in, or it is part
763 -- of some other declaration, or it is generated implicitly by some
764 -- other declaration.
765 isImplicitTyThing :: TyThing -> Bool
766 isImplicitTyThing (ADataCon _)  = True
767 isImplicitTyThing (AnId     id) = isImplicitId id
768 isImplicitTyThing (AClass   _)  = False
769 isImplicitTyThing (ATyCon   tc) = isImplicitTyCon tc
770
771         -- For newtypes and indexed data types, add the implicit coercion tycon
772 implicitCoTyCon tc 
773   = map ATyCon . catMaybes $ [newTyConCo_maybe tc, 
774                               tyConFamilyCoercion_maybe tc]
775
776 extras_plus thing = thing : implicitTyThings thing
777
778 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
779 extendTypeEnvWithIds env ids
780   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
781 \end{code}
782
783 %************************************************************************
784 %*                                                                      *
785                 TypeEnv
786 %*                                                                      *
787 %************************************************************************
788
789 \begin{code}
790 type TypeEnv = NameEnv TyThing
791
792 emptyTypeEnv    :: TypeEnv
793 typeEnvElts     :: TypeEnv -> [TyThing]
794 typeEnvClasses  :: TypeEnv -> [Class]
795 typeEnvTyCons   :: TypeEnv -> [TyCon]
796 typeEnvIds      :: TypeEnv -> [Id]
797 typeEnvDataCons :: TypeEnv -> [DataCon]
798 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
799
800 emptyTypeEnv        = emptyNameEnv
801 typeEnvElts     env = nameEnvElts env
802 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
803 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
804 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
805 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
806
807 mkTypeEnv :: [TyThing] -> TypeEnv
808 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
809                 
810 lookupTypeEnv = lookupNameEnv
811
812 -- Extend the type environment
813 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
814 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
815
816 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
817 extendTypeEnvList env things = foldl extendTypeEnv env things
818 \end{code}
819
820 \begin{code}
821 lookupType :: DynFlags
822            -> HomePackageTable
823            -> PackageTypeEnv
824            -> Name
825            -> Maybe TyThing
826
827 lookupType dflags hpt pte name
828   -- in one-shot, we don't use the HPT
829   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
830   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
831        lookupNameEnv (md_types (hm_details hm)) name
832   | otherwise
833   = lookupNameEnv pte name
834   where mod = nameModule name
835         this_pkg = thisPackage dflags
836 \end{code}
837
838 \begin{code}
839 tyThingTyCon (ATyCon tc) = tc
840 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
841
842 tyThingClass (AClass cls) = cls
843 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
844
845 tyThingDataCon (ADataCon dc) = dc
846 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
847
848 tyThingId (AnId id) = id
849 tyThingId other     = pprPanic "tyThingId" (ppr other)
850 \end{code}
851
852 %************************************************************************
853 %*                                                                      *
854 \subsection{Auxiliary types}
855 %*                                                                      *
856 %************************************************************************
857
858 These types are defined here because they are mentioned in ModDetails,
859 but they are mostly elaborated elsewhere
860
861 \begin{code}
862 mkIfaceVerCache :: [(Version,IfaceDecl)]
863                 -> (OccName -> Maybe (OccName, Version))
864 mkIfaceVerCache pairs 
865   = \occ -> lookupOccEnv env occ
866   where
867     env = foldr add_decl emptyOccEnv pairs
868     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
869       where
870           decl_name = ifName d
871           env1 = extendOccEnv env0 decl_name (decl_name, v)
872           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
873
874 emptyIfaceVerCache :: OccName -> Maybe (OccName, Version)
875 emptyIfaceVerCache occ = Nothing
876
877 ------------------ Deprecations -------------------------
878 data Deprecs a
879   = NoDeprecs
880   | DeprecAll DeprecTxt -- Whole module deprecated
881   | DeprecSome a        -- Some specific things deprecated
882   deriving( Eq )
883
884 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
885 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
886         -- Keep the OccName so we can flatten the NameEnv to
887         -- get an IfaceDeprecs from a Deprecations
888         -- Only an OccName is needed, because a deprecation always
889         -- applies to things defined in the module in which the
890         -- deprecation appears.
891
892 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
893 mkIfaceDepCache NoDeprecs         = \n -> Nothing
894 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
895 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
896
897 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
898 emptyIfaceDepCache n = Nothing
899
900 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
901 plusDeprecs d NoDeprecs = d
902 plusDeprecs NoDeprecs d = d
903 plusDeprecs d (DeprecAll t) = DeprecAll t
904 plusDeprecs (DeprecAll t) d = DeprecAll t
905 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
906 \end{code}
907
908
909 \begin{code}
910 type Avails       = [AvailInfo]
911 type AvailInfo    = GenAvailInfo Name
912 type RdrAvailInfo = GenAvailInfo OccName
913
914 data GenAvailInfo name  = Avail name     -- An ordinary identifier
915                         | AvailTC name   -- The name of the type or class
916                                   [name] -- The available pieces of type/class.
917                                          -- NB: If the type or class is itself
918                                          -- to be in scope, it must be in this list.
919                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
920                         deriving( Eq )
921                         -- Equality used when deciding if the interface has changed
922
923 type IfaceExport = (Module, [GenAvailInfo OccName])
924
925 availsToNameSet :: [AvailInfo] -> NameSet
926 availsToNameSet avails = foldr add emptyNameSet avails
927       where add avail set = addListToNameSet set (availNames avail)
928
929 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
930 availsToNameEnv avails = foldr add emptyNameEnv avails
931      where add avail env = extendNameEnvList env
932                                 (zip (availNames avail) (repeat avail))
933
934 availName :: GenAvailInfo name -> name
935 availName (Avail n)     = n
936 availName (AvailTC n _) = n
937
938 availNames :: GenAvailInfo name -> [name]
939 availNames (Avail n)      = [n]
940 availNames (AvailTC n ns) = ns
941
942 instance Outputable n => Outputable (GenAvailInfo n) where
943    ppr = pprAvail
944
945 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
946 pprAvail (Avail n)      = ppr n
947 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
948 \end{code}
949
950 \begin{code}
951 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
952 mkIfaceFixCache pairs 
953   = \n -> lookupOccEnv env n `orElse` defaultFixity
954   where
955    env = mkOccEnv pairs
956
957 emptyIfaceFixCache :: OccName -> Fixity
958 emptyIfaceFixCache n = defaultFixity
959
960 -- This fixity environment is for source code only
961 type FixityEnv = NameEnv FixItem
962
963 -- We keep the OccName in the range so that we can generate an interface from it
964 data FixItem = FixItem OccName Fixity SrcSpan
965
966 instance Outputable FixItem where
967   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
968
969 emptyFixityEnv :: FixityEnv
970 emptyFixityEnv = emptyNameEnv
971
972 lookupFixity :: FixityEnv -> Name -> Fixity
973 lookupFixity env n = case lookupNameEnv env n of
974                         Just (FixItem _ fix _) -> fix
975                         Nothing                -> defaultFixity
976 \end{code}
977
978
979 %************************************************************************
980 %*                                                                      *
981 \subsection{WhatsImported}
982 %*                                                                      *
983 %************************************************************************
984
985 \begin{code}
986 type WhetherHasOrphans   = Bool
987         -- An "orphan" is 
988         --      * an instance decl in a module other than the defn module for 
989         --              one of the tycons or classes in the instance head
990         --      * a transformation rule in a module other than the one defining
991         --              the function in the head of the rule.
992
993 type WhetherHasFamInst = Bool        -- This module defines family instances?
994
995 type IsBootInterface = Bool
996
997 -- Dependency info about modules and packages below this one
998 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
999 -- The orphan modules in `dep_orphs' do *not* include family instance orphans,
1000 -- as they are anyway included in `dep_finsts'.
1001 --
1002 -- Invariant: the dependencies of a module M never includes M
1003 -- Invariant: the lists are unordered, with no duplicates
1004 data Dependencies
1005   = Deps { dep_mods   :: [(ModuleName,      -- Home-package module dependencies
1006                            IsBootInterface)]
1007          , dep_pkgs   :: [PackageId]        -- External package dependencies
1008          , dep_orphs  :: [Module]           -- Orphan modules (whether home or
1009                                             -- external pkg)
1010          , dep_finsts :: [Module]           -- Modules that contain family
1011                                             -- instances (whether home or
1012                                             -- external pkg)
1013          }
1014   deriving( Eq )
1015         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1016
1017 noDependencies :: Dependencies
1018 noDependencies = Deps [] [] [] []
1019           
1020 data Usage
1021   = Usage { usg_name     :: ModuleName,                 -- Name of the module
1022             usg_mod      :: Version,                    -- Module version
1023             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
1024                 -- NB. usages are for parent names only, eg. tycon but not constructors.
1025             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
1026             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
1027                                                         -- modules this will always be initialVersion)
1028     }       deriving( Eq )
1029         -- This type doesn't let you say "I imported f but none of the rules in
1030         -- the module". If you use anything in the module you get its rule version
1031         -- So if the rules change, you'll recompile, even if you don't use them.
1032         -- This is easy to implement, and it's safer: you might not have used the rules last
1033         -- time round, but if someone has added a new rule you might need it this time
1034
1035         -- The export list field is (Just v) if we depend on the export list:
1036         --      i.e. we imported the module directly, whether or not we
1037         --           enumerated the things we imported, or just imported everything
1038         -- We need to recompile if M's exports change, because 
1039         -- if the import was    import M,       we might now have a name clash in the 
1040         --                                      importing module.
1041         -- if the import was    import M(x)     M might no longer export x
1042         -- The only way we don't depend on the export list is if we have
1043         --                      import M()
1044         -- And of course, for modules that aren't imported directly we don't
1045         -- depend on their export lists
1046 \end{code}
1047
1048
1049 %************************************************************************
1050 %*                                                                      *
1051                 The External Package State
1052 %*                                                                      *
1053 %************************************************************************
1054
1055 \begin{code}
1056 type PackageTypeEnv    = TypeEnv
1057 type PackageRuleBase   = RuleBase
1058 type PackageInstEnv    = InstEnv
1059 type PackageFamInstEnv = FamInstEnv
1060 type PackageVectInfo   = VectInfo
1061
1062 data ExternalPackageState
1063   = EPS {
1064         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1065                 -- In OneShot mode (only), home-package modules
1066                 -- accumulate in the external package state, and are
1067                 -- sucked in lazily.  For these home-pkg modules
1068                 -- (only) we need to record which are boot modules.
1069                 -- We set this field after loading all the
1070                 -- explicitly-imported interfaces, but before doing
1071                 -- anything else
1072                 --
1073                 -- The ModuleName part is not necessary, but it's useful for
1074                 -- debug prints, and it's convenient because this field comes
1075                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
1076
1077         eps_PIT :: !PackageIfaceTable,
1078                 -- The ModuleIFaces for modules in external packages
1079                 -- whose interfaces we have opened
1080                 -- The declarations in these interface files are held in
1081                 -- eps_decls, eps_inst_env, eps_fam_inst_env, eps_rules
1082                 -- (below), not in the mi_decls fields of the iPIT.  
1083                 -- What _is_ in the iPIT is:
1084                 --      * The Module 
1085                 --      * Version info
1086                 --      * Its exports
1087                 --      * Fixities
1088                 --      * Deprecations
1089
1090         eps_PTE :: !PackageTypeEnv,        -- Domain = external-package modules
1091
1092         eps_inst_env     :: !PackageInstEnv,   -- The total InstEnv accumulated
1093                                                -- from all the external-package
1094                                                -- modules 
1095         eps_fam_inst_env :: !PackageFamInstEnv,-- Ditto FamInstEnv
1096         eps_rule_base    :: !PackageRuleBase,  -- Ditto RuleEnv
1097         eps_vect_info    :: !PackageVectInfo,  -- Ditto VectInfo
1098
1099         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- identifies family
1100                                                        -- instances of each mod 
1101         eps_stats :: !EpsStats
1102   }
1103
1104 -- "In" means read from iface files
1105 -- "Out" means actually sucked in and type-checked
1106 data EpsStats = EpsStats { n_ifaces_in
1107                          , n_decls_in, n_decls_out 
1108                          , n_rules_in, n_rules_out
1109                          , n_insts_in, n_insts_out :: !Int }
1110
1111 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1112 -- Add stats for one newly-read interface
1113 addEpsInStats stats n_decls n_insts n_rules
1114   = stats { n_ifaces_in = n_ifaces_in stats + 1
1115           , n_decls_in  = n_decls_in stats + n_decls
1116           , n_insts_in  = n_insts_in stats + n_insts
1117           , n_rules_in  = n_rules_in stats + n_rules }
1118 \end{code}
1119
1120 The NameCache makes sure that there is just one Unique assigned for
1121 each original name; i.e. (module-name, occ-name) pair.  The Name is
1122 always stored as a Global, and has the SrcLoc of its binding location.
1123 Actually that's not quite right.  When we first encounter the original
1124 name, we might not be at its binding site (e.g. we are reading an
1125 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1126 its binding site, we fix it up.
1127
1128 \begin{code}
1129 data NameCache
1130  = NameCache {  nsUniqs :: UniqSupply,
1131                 -- Supply of uniques
1132                 nsNames :: OrigNameCache,
1133                 -- Ensures that one original name gets one unique
1134                 nsIPs   :: OrigIParamCache
1135                 -- Ensures that one implicit parameter name gets one unique
1136    }
1137
1138 type OrigNameCache   = ModuleEnv (OccEnv Name)
1139 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
1140 \end{code}
1141
1142
1143
1144 %************************************************************************
1145 %*                                                                      *
1146                 The module graph and ModSummary type
1147         A ModSummary is a node in the compilation manager's
1148         dependency graph, and it's also passed to hscMain
1149 %*                                                                      *
1150 %************************************************************************
1151
1152 A ModuleGraph contains all the nodes from the home package (only).  
1153 There will be a node for each source module, plus a node for each hi-boot
1154 module.
1155
1156 \begin{code}
1157 type ModuleGraph = [ModSummary]  -- The module graph, 
1158                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
1159
1160 emptyMG :: ModuleGraph
1161 emptyMG = []
1162
1163 -- The nodes of the module graph are
1164 --      EITHER a regular Haskell source module
1165 --      OR     a hi-boot source module
1166
1167 data ModSummary
1168    = ModSummary {
1169         ms_mod       :: Module,                 -- Identity of the module
1170         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
1171         ms_location  :: ModLocation,            -- Location
1172         ms_hs_date   :: ClockTime,              -- Timestamp of source file
1173         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
1174         ms_srcimps   :: [Located ModuleName],   -- Source imports
1175         ms_imps      :: [Located ModuleName],   -- Non-source imports
1176         ms_hspp_file :: FilePath,               -- Filename of preprocessed source.
1177         ms_hspp_opts :: DynFlags,               -- Cached flags from OPTIONS, INCLUDE
1178                                                 -- and LANGUAGE pragmas.
1179         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
1180      }
1181
1182 ms_mod_name :: ModSummary -> ModuleName
1183 ms_mod_name = moduleName . ms_mod
1184
1185 -- The ModLocation contains both the original source filename and the
1186 -- filename of the cleaned-up source file after all preprocessing has been
1187 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1188 -- all files anyway, and there's no point in doing this twice -- just 
1189 -- park the result in a temp file, put the name of it in the location,
1190 -- and let @compile@ read from that file on the way back up.
1191
1192 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1193 -- the ms_hs_date and imports can, of course, change
1194
1195 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1196 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1197 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1198 msObjFilePath ms = ml_obj_file (ms_location ms)
1199
1200 isBootSummary :: ModSummary -> Bool
1201 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1202
1203 instance Outputable ModSummary where
1204    ppr ms
1205       = sep [text "ModSummary {",
1206              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1207                           text "ms_mod =" <+> ppr (ms_mod ms) 
1208                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1209                           text "ms_imps =" <+> ppr (ms_imps ms),
1210                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1211              char '}'
1212             ]
1213
1214 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1215 showModMsg target recomp mod_summary
1216   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1217                     char '(', text (msHsFilePath mod_summary) <> comma,
1218                     case target of
1219                       HscInterpreted | recomp 
1220                                  -> text "interpreted"
1221                       HscNothing -> text "nothing"
1222                       _other     -> text (msObjFilePath mod_summary),
1223                     char ')'])
1224  where 
1225     mod     = moduleName (ms_mod mod_summary)
1226     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1227 \end{code}
1228
1229
1230 %************************************************************************
1231 %*                                                                      *
1232 \subsection{Hpc Support}
1233 %*                                                                      *
1234 %************************************************************************
1235
1236 \begin{code}
1237 data HpcInfo = HpcInfo 
1238      { hpcInfoTickCount :: Int 
1239      , hpcInfoHash      :: Int  
1240      }
1241      | NoHpcInfo
1242
1243 noHpcInfo :: HpcInfo
1244 noHpcInfo = NoHpcInfo
1245 \end{code}
1246
1247 %************************************************************************
1248 %*                                                                      *
1249 \subsection{Vectorisation Support}
1250 %*                                                                      *
1251 %************************************************************************
1252
1253 The following information is generated and consumed by the vectorisation
1254 subsystem.  It communicates the vectorisation status of declarations from one
1255 module to another.
1256
1257 Why do we need both f and f_CC in the ModGuts/ModDetails/EPS version VectInfo
1258 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1259 closure conversion, we need to know `f_CC', whose `Var' we cannot lookup based
1260 on just the OccName easily in a Core pass.
1261
1262 \begin{code}
1263 -- ModGuts/ModDetails/EPS version
1264 data VectInfo      
1265   = VectInfo {
1266       vectInfoCCVar     :: VarEnv  (Var    , Var  ),   -- (f, f_CC) keyed on f
1267       vectInfoCCTyCon   :: NameEnv (TyCon  , TyCon),   -- (T, T_CC) keyed on T
1268       vectInfoCCDataCon :: NameEnv (DataCon, DataCon), -- (C, C_CC) keyed on C
1269       vectInfoCCIso     :: NameEnv (TyCon  , Var)      -- (T, isoT) keyed on T
1270     }
1271     -- all of this is always tidy, even in ModGuts
1272
1273 -- ModIface version
1274 data IfaceVectInfo 
1275   = IfaceVectInfo {
1276       ifaceVectInfoCCVar        :: [Name],
1277         -- all variables in here have a closure-converted variant;
1278         -- the name of the CC'ed variant is determined by `mkCloOcc'
1279       ifaceVectInfoCCTyCon      :: [Name],
1280         -- all tycons in here have a closure-converted variant;
1281         -- the name of the CC'ed variant and those of its data constructors are
1282         -- determined by `mkCloTyConOcc' and `mkCloDataConOcc'; the names of
1283         -- the isomorphisms is determined by `mkCloIsoOcc'
1284       ifaceVectInfoCCTyConReuse :: [Name]              
1285         -- the closure-converted form of all the tycons in here coincids with
1286         -- the unconverted from; the names of the isomorphisms is determined
1287         -- by `mkCloIsoOcc'
1288     }
1289
1290 noVectInfo :: VectInfo
1291 noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv
1292
1293 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1294 plusVectInfo vi1 vi2 = 
1295   VectInfo (vectInfoCCVar     vi1 `plusVarEnv`  vectInfoCCVar     vi2)
1296            (vectInfoCCTyCon   vi1 `plusNameEnv` vectInfoCCTyCon   vi2)
1297            (vectInfoCCDataCon vi1 `plusNameEnv` vectInfoCCDataCon vi2)
1298            (vectInfoCCIso     vi1 `plusNameEnv` vectInfoCCIso     vi2)
1299
1300 noIfaceVectInfo :: IfaceVectInfo
1301 noIfaceVectInfo = IfaceVectInfo [] [] []
1302 \end{code}
1303
1304 %************************************************************************
1305 %*                                                                      *
1306 \subsection{Linkable stuff}
1307 %*                                                                      *
1308 %************************************************************************
1309
1310 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1311 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1312
1313 \begin{code}
1314 data Linkable = LM {
1315   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1316                                         -- (i.e. when the bytecodes were produced,
1317                                         --       or the mod date on the files)
1318   linkableModule   :: Module,           -- Should be Module, but see below
1319   linkableUnlinked :: [Unlinked]
1320  }
1321
1322 isObjectLinkable :: Linkable -> Bool
1323 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1324   where unlinked = linkableUnlinked l
1325         -- A linkable with no Unlinked's is treated as a BCO.  We can
1326         -- generate a linkable with no Unlinked's as a result of
1327         -- compiling a module in HscNothing mode, and this choice
1328         -- happens to work well with checkStability in module GHC.
1329
1330 instance Outputable Linkable where
1331    ppr (LM when_made mod unlinkeds)
1332       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1333         $$ nest 3 (ppr unlinkeds)
1334
1335 -------------------------------------------
1336 data Unlinked
1337    = DotO FilePath
1338    | DotA FilePath
1339    | DotDLL FilePath
1340    | BCOs CompiledByteCode
1341
1342 #ifndef GHCI
1343 data CompiledByteCode = NoByteCode
1344 #endif
1345
1346 instance Outputable Unlinked where
1347    ppr (DotO path)   = text "DotO" <+> text path
1348    ppr (DotA path)   = text "DotA" <+> text path
1349    ppr (DotDLL path) = text "DotDLL" <+> text path
1350 #ifdef GHCI
1351    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1352 #else
1353    ppr (BCOs bcos)   = text "No byte code"
1354 #endif
1355
1356 isObject (DotO _)   = True
1357 isObject (DotA _)   = True
1358 isObject (DotDLL _) = True
1359 isObject _          = False
1360
1361 isInterpretable = not . isObject
1362
1363 nameOfObject (DotO fn)   = fn
1364 nameOfObject (DotA fn)   = fn
1365 nameOfObject (DotDLL fn) = fn
1366 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1367
1368 byteCodeOfObject (BCOs bc) = bc
1369 byteCodeOfObject other     = pprPanic "byteCodeOfObject" (ppr other)
1370 \end{code}
1371
1372 %************************************************************************
1373 %*                                                                      *
1374 \subsection{Breakpoint Support}
1375 %*                                                                      *
1376 %************************************************************************
1377
1378 \begin{code}
1379 type BreakIndex = Int
1380
1381 -- | all the information about the breakpoints for a given module
1382 data ModBreaks
1383    = ModBreaks
1384    { modBreaks_flags :: BreakArray
1385         -- The array of flags, one per breakpoint, 
1386         -- indicating which breakpoints are enabled.
1387    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
1388         -- An array giving the source span of each breakpoint.
1389    , modBreaks_vars :: !(Array BreakIndex [OccName])
1390         -- An array giving the names of the free variables at each breakpoint.
1391    }
1392
1393 emptyModBreaks :: ModBreaks
1394 emptyModBreaks = ModBreaks
1395    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
1396          -- Todo: can we avoid this? 
1397    , modBreaks_locs = array (0,-1) []
1398    , modBreaks_vars = array (0,-1) []
1399    }
1400 \end{code}