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