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