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