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