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