Handle unlifted tycons and tuples correctly during vectorisation
[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(..), noHpcInfo,
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      }
483
484 -- Should be able to construct ModDetails from mi_decls in ModIface
485 data ModDetails
486    = ModDetails {
487         -- The next two fields are created by the typechecker
488         md_exports   :: [AvailInfo],
489         md_types     :: !TypeEnv,
490         md_insts     :: ![Instance],  -- Dfun-ids for the instances in this module
491         md_fam_insts :: ![FamInst],
492         md_rules     :: ![CoreRule],  -- Domain may include Ids from other modules
493         md_modBreaks :: !ModBreaks,   -- Breakpoint information for this module 
494         md_vect_info :: !VectInfo     -- Vectorisation information
495      }
496
497 emptyModDetails = ModDetails { md_types = emptyTypeEnv,
498                                md_exports = [],
499                                md_insts     = [],
500                                md_rules     = [],
501                                md_fam_insts = [],
502                                md_modBreaks = emptyModBreaks,
503                                md_vect_info = noVectInfo
504                              } 
505
506 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
507 -- There is only one ModGuts at any time, the one for the module
508 -- being compiled right now.  Once it is compiled, a ModIface and 
509 -- ModDetails are extracted and the ModGuts is dicarded.
510
511 data ModGuts
512   = ModGuts {
513         mg_module    :: !Module,
514         mg_boot      :: IsBootInterface, -- Whether it's an hs-boot module
515         mg_exports   :: ![AvailInfo],    -- What it exports
516         mg_deps      :: !Dependencies,   -- What is below it, directly or
517                                          --   otherwise 
518         mg_dir_imps  :: ![Module],       -- Directly-imported modules; used to
519                                          --     generate initialisation code
520         mg_usages    :: ![Usage],        -- Version info for what it needed
521
522         mg_rdr_env   :: !GlobalRdrEnv,   -- Top-level lexical environment
523         mg_fix_env   :: !FixityEnv,      -- Fixity env, for things declared in
524                                          --   this module 
525
526         mg_inst_env     :: InstEnv,      -- Class instance enviroment fro
527                                          -- *home-package* modules (including
528                                          -- this one); c.f. tcg_inst_env
529         mg_fam_inst_env :: FamInstEnv,   -- Type-family instance enviroment
530                                          -- for *home-package* modules (including
531                                          -- this one); c.f. tcg_fam_inst_env
532
533         mg_types     :: !TypeEnv,
534         mg_insts     :: ![Instance],     -- Instances 
535         mg_fam_insts :: ![FamInst],      -- Instances 
536         mg_rules     :: ![CoreRule],     -- Rules from this module
537         mg_binds     :: ![CoreBind],     -- Bindings for this module
538         mg_foreign   :: !ForeignStubs,
539         mg_deprecs   :: !Deprecations,   -- Deprecations declared in the module
540         mg_hpc_info  :: !HpcInfo,        -- info about coverage tick boxes
541         mg_modBreaks :: !ModBreaks,
542         mg_vect_info :: !VectInfo        -- Pool of vectorised declarations
543     }
544
545 -- The ModGuts takes on several slightly different forms:
546 --
547 -- After simplification, the following fields change slightly:
548 --      mg_rules        Orphan rules only (local ones now attached to binds)
549 --      mg_binds        With rules attached
550
551
552 ---------------------------------------------------------
553 -- The Tidy pass forks the information about this module: 
554 --      * one lot goes to interface file generation (ModIface)
555 --        and later compilations (ModDetails)
556 --      * the other lot goes to code generation (CgGuts)
557 data CgGuts 
558   = CgGuts {
559         cg_module   :: !Module,
560
561         cg_tycons   :: [TyCon],
562                 -- Algebraic data types (including ones that started
563                 -- life as classes); generate constructors and info
564                 -- tables Includes newtypes, just for the benefit of
565                 -- External Core
566
567         cg_binds    :: [CoreBind],
568                 -- The tidied main bindings, including
569                 -- previously-implicit bindings for record and class
570                 -- selectors, and data construtor wrappers.  But *not*
571                 -- data constructor workers; reason: we we regard them
572                 -- as part of the code-gen of tycons
573
574         cg_dir_imps :: ![Module],
575                 -- Directly-imported modules; used to generate
576                 -- initialisation code
577
578         cg_foreign  :: !ForeignStubs,   
579         cg_dep_pkgs :: ![PackageId],    -- Used to generate #includes for C code gen
580         cg_hpc_info :: !HpcInfo         -- info about coverage tick boxes
581     }
582
583 -----------------------------------
584 data ModImports
585   = ModImports {
586         imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
587                                                 -- Boolean is true if we imported the whole
588                                                 --      module (apart, perhaps, from hiding some)
589         imp_pkg_mods   :: !ModuleSet,           -- Non-home-package modules on which we depend,
590                                                 --      directly or indirectly
591         imp_home_names :: !NameSet              -- Home package things on which we depend,
592                                                 --      directly or indirectly
593     }
594
595 -----------------------------------
596 data ForeignStubs = NoStubs
597                   | ForeignStubs
598                         SDoc            -- Header file prototypes for
599                                         --      "foreign exported" functions
600                         SDoc            -- C stubs to use when calling
601                                         --      "foreign exported" functions
602                         [FastString]    -- Headers that need to be included
603                                         --      into C code generated for this module
604                         [Id]            -- Foreign-exported binders
605                                         --      we have to generate code to register these
606
607 \end{code}
608
609 \begin{code}
610 emptyModIface :: Module -> ModIface
611 emptyModIface mod
612   = ModIface { mi_module   = mod,
613                mi_mod_vers = initialVersion,
614                mi_orphan   = False,
615                mi_finsts   = False,
616                mi_boot     = False,
617                mi_deps     = noDependencies,
618                mi_usages   = [],
619                mi_exports  = [],
620                mi_exp_vers = initialVersion,
621                mi_fixities = [],
622                mi_deprecs  = NoDeprecs,
623                mi_insts     = [],
624                mi_fam_insts = [],
625                mi_rules     = [],
626                mi_decls     = [],
627                mi_globals   = Nothing,
628                mi_rule_vers = initialVersion,
629                mi_vect_info = noIfaceVectInfo,
630                mi_dep_fn = emptyIfaceDepCache,
631                mi_fix_fn = emptyIfaceFixCache,
632                mi_ver_fn = emptyIfaceVerCache
633     }           
634 \end{code}
635
636
637 %************************************************************************
638 %*                                                                      *
639 \subsection{The interactive context}
640 %*                                                                      *
641 %************************************************************************
642
643 \begin{code}
644 data InteractiveContext 
645   = InteractiveContext { 
646         ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
647                                         -- these modules
648
649         ic_exports :: [Module],         -- Include just the exports of these
650                                         -- modules
651
652         ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
653                                         -- ic_toplev_scope and ic_exports
654
655         ic_tmp_ids :: [Id],             -- Names bound during interaction.
656                                         -- Later Ids shadow
657                                         -- earlier ones with the same OccName.
658
659         ic_tyvars :: TyVarSet           -- skolem type variables free in
660                                         -- ic_tmp_ids.  These arise at
661                                         -- breakpoints in a polymorphic 
662                                         -- context, where we have only partial
663                                         -- type information.
664
665 #ifdef GHCI
666         , ic_resume :: [Resume]         -- the stack of breakpoint contexts
667 #endif
668     }
669
670
671 emptyInteractiveContext
672   = InteractiveContext { ic_toplev_scope = [],
673                          ic_exports = [],
674                          ic_rn_gbl_env = emptyGlobalRdrEnv,
675                          ic_tmp_ids = [],
676                          ic_tyvars = emptyVarSet
677 #ifdef GHCI
678                          , ic_resume = []
679 #endif
680                        }
681
682 icPrintUnqual :: InteractiveContext -> PrintUnqualified
683 icPrintUnqual ictxt = mkPrintUnqualified (ic_rn_gbl_env ictxt)
684
685
686 extendInteractiveContext
687         :: InteractiveContext
688         -> [Id]
689         -> TyVarSet
690         -> InteractiveContext
691 extendInteractiveContext ictxt ids tyvars
692   = ictxt { ic_tmp_ids =  ic_tmp_ids ictxt ++ ids,
693                           -- NB. must be this way around, because we want
694                           -- new ids to shadow existing bindings.
695             ic_tyvars   = ic_tyvars ictxt `unionVarSet` tyvars }
696
697
698 substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
699 substInteractiveContext ictxt subst | isEmptyTvSubst subst = ictxt
700 substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst =
701    let ids'     = map (\id -> id `setIdType` substTy subst (idType id)) ids
702        subst_dom= varEnvKeys$ getTvSubstEnv subst
703        subst_ran= varEnvElts$ getTvSubstEnv subst
704        new_tvs  = [ tv | Just tv <- map getTyVar_maybe subst_ran]  
705        ic_tyvars'= (`delVarSetListByKey` subst_dom) 
706                  . (`extendVarSetList`   new_tvs)
707                    $ ic_tyvars ictxt
708     in ictxt { ic_tmp_ids = ids'
709              , ic_tyvars   = ic_tyvars' }
710
711           where delVarSetListByKey = foldl' delVarSetByKey
712 \end{code}
713
714 %************************************************************************
715 %*                                                                      *
716         Building a PrintUnqualified             
717 %*                                                                      *
718 %************************************************************************
719
720 \begin{code}
721 mkPrintUnqualified :: GlobalRdrEnv -> PrintUnqualified
722 mkPrintUnqualified env = (qual_name, qual_mod)
723   where
724   qual_name mod occ     -- The (mod,occ) pair is the original name of the thing
725         | [gre] <- unqual_gres, right_name gre = Nothing
726                 -- If there's a unique entity that's in scope unqualified with 'occ'
727                 -- AND that entity is the right one, then we can use the unqualified name
728
729         | [gre] <- qual_gres = Just (get_qual_mod (gre_prov gre))
730
731         | null qual_gres = Just (moduleName mod)
732                 -- it isn't in scope at all, this probably shouldn't happen,
733                 -- but we'll qualify it by the original module anyway.
734
735         | otherwise = panic "mkPrintUnqualified"
736       where
737         right_name gre = nameModule (gre_name gre) == mod
738
739         unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
740         qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
741
742         get_qual_mod LocalDef      = moduleName mod
743         get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
744
745   qual_mod mod = Nothing       -- For now, we never qualify module names with their packages
746 \end{code}
747
748
749 %************************************************************************
750 %*                                                                      *
751                 TyThing
752 %*                                                                      *
753 %************************************************************************
754
755 \begin{code}
756 implicitTyThings :: TyThing -> [TyThing]
757 -- If you change this, make sure you change LoadIface.ifaceDeclSubBndrs in sync
758
759 implicitTyThings (AnId id)   = []
760
761         -- For type constructors, add the data cons (and their extras),
762         -- and the selectors and generic-programming Ids too
763         --
764         -- Newtypes don't have a worker Id, so don't generate that?
765 implicitTyThings (ATyCon tc) = implicitCoTyCon tc ++
766                                map AnId (tyConSelIds tc) ++ 
767                                concatMap (extras_plus . ADataCon) 
768                                          (tyConDataCons tc)
769                      
770         -- For classes, add the class selector Ids, and assoicated TyCons
771         -- and the class TyCon too (and its extras)
772 implicitTyThings (AClass cl) 
773   = map AnId (classSelIds cl) ++
774     map ATyCon (classATs cl) ++
775         -- No extras_plus for the classATs, because they
776         -- are only the family decls; they have no implicit things
777     extras_plus (ATyCon (classTyCon cl))
778
779         -- For data cons add the worker and wrapper (if any)
780 implicitTyThings (ADataCon dc) = map AnId (dataConImplicitIds dc)
781
782 -- | returns 'True' if there should be no interface-file declaration
783 -- for this thing on its own: either it is built-in, or it is part
784 -- of some other declaration, or it is generated implicitly by some
785 -- other declaration.
786 isImplicitTyThing :: TyThing -> Bool
787 isImplicitTyThing (ADataCon _)  = True
788 isImplicitTyThing (AnId     id) = isImplicitId id
789 isImplicitTyThing (AClass   _)  = False
790 isImplicitTyThing (ATyCon   tc) = isImplicitTyCon tc
791
792         -- For newtypes and indexed data types, add the implicit coercion tycon
793 implicitCoTyCon tc 
794   = map ATyCon . catMaybes $ [newTyConCo_maybe tc, 
795                               tyConFamilyCoercion_maybe tc]
796
797 extras_plus thing = thing : implicitTyThings thing
798
799 extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
800 extendTypeEnvWithIds env ids
801   = extendNameEnvList env [(getName id, AnId id) | id <- ids]
802 \end{code}
803
804 %************************************************************************
805 %*                                                                      *
806                 TypeEnv
807 %*                                                                      *
808 %************************************************************************
809
810 \begin{code}
811 type TypeEnv = NameEnv TyThing
812
813 emptyTypeEnv    :: TypeEnv
814 typeEnvElts     :: TypeEnv -> [TyThing]
815 typeEnvClasses  :: TypeEnv -> [Class]
816 typeEnvTyCons   :: TypeEnv -> [TyCon]
817 typeEnvIds      :: TypeEnv -> [Id]
818 typeEnvDataCons :: TypeEnv -> [DataCon]
819 lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
820
821 emptyTypeEnv        = emptyNameEnv
822 typeEnvElts     env = nameEnvElts env
823 typeEnvClasses  env = [cl | AClass cl   <- typeEnvElts env]
824 typeEnvTyCons   env = [tc | ATyCon tc   <- typeEnvElts env] 
825 typeEnvIds      env = [id | AnId id     <- typeEnvElts env] 
826 typeEnvDataCons env = [dc | ADataCon dc <- typeEnvElts env] 
827
828 mkTypeEnv :: [TyThing] -> TypeEnv
829 mkTypeEnv things = extendTypeEnvList emptyTypeEnv things
830                 
831 lookupTypeEnv = lookupNameEnv
832
833 -- Extend the type environment
834 extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
835 extendTypeEnv env thing = extendNameEnv env (getName thing) thing 
836
837 extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
838 extendTypeEnvList env things = foldl extendTypeEnv env things
839 \end{code}
840
841 \begin{code}
842 lookupType :: DynFlags
843            -> HomePackageTable
844            -> PackageTypeEnv
845            -> Name
846            -> Maybe TyThing
847
848 lookupType dflags hpt pte name
849   -- in one-shot, we don't use the HPT
850   | not (isOneShot (ghcMode dflags)) && modulePackageId mod == this_pkg 
851   = do hm <- lookupUFM hpt (moduleName mod) -- Maybe monad
852        lookupNameEnv (md_types (hm_details hm)) name
853   | otherwise
854   = lookupNameEnv pte name
855   where mod = nameModule name
856         this_pkg = thisPackage dflags
857 \end{code}
858
859 \begin{code}
860 tyThingTyCon (ATyCon tc) = tc
861 tyThingTyCon other       = pprPanic "tyThingTyCon" (ppr other)
862
863 tyThingClass (AClass cls) = cls
864 tyThingClass other        = pprPanic "tyThingClass" (ppr other)
865
866 tyThingDataCon (ADataCon dc) = dc
867 tyThingDataCon other         = pprPanic "tyThingDataCon" (ppr other)
868
869 tyThingId (AnId id) = id
870 tyThingId other     = pprPanic "tyThingId" (ppr other)
871 \end{code}
872
873 %************************************************************************
874 %*                                                                      *
875 \subsection{Auxiliary types}
876 %*                                                                      *
877 %************************************************************************
878
879 These types are defined here because they are mentioned in ModDetails,
880 but they are mostly elaborated elsewhere
881
882 \begin{code}
883 mkIfaceVerCache :: [(Version,IfaceDecl)]
884                 -> (OccName -> Maybe (OccName, Version))
885 mkIfaceVerCache pairs 
886   = \occ -> lookupOccEnv env occ
887   where
888     env = foldr add_decl emptyOccEnv pairs
889     add_decl (v,d) env0 = foldr add_imp env1 (ifaceDeclSubBndrs d)
890       where
891           decl_name = ifName d
892           env1 = extendOccEnv env0 decl_name (decl_name, v)
893           add_imp bndr env = extendOccEnv env bndr (decl_name, v)
894
895 emptyIfaceVerCache :: OccName -> Maybe (OccName, Version)
896 emptyIfaceVerCache occ = Nothing
897
898 ------------------ Deprecations -------------------------
899 data Deprecs a
900   = NoDeprecs
901   | DeprecAll DeprecTxt -- Whole module deprecated
902   | DeprecSome a        -- Some specific things deprecated
903   deriving( Eq )
904
905 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
906 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
907         -- Keep the OccName so we can flatten the NameEnv to
908         -- get an IfaceDeprecs from a Deprecations
909         -- Only an OccName is needed, because a deprecation always
910         -- applies to things defined in the module in which the
911         -- deprecation appears.
912
913 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
914 mkIfaceDepCache NoDeprecs         = \n -> Nothing
915 mkIfaceDepCache (DeprecAll t)     = \n -> Just t
916 mkIfaceDepCache (DeprecSome pairs) = lookupOccEnv (mkOccEnv pairs) . nameOccName
917
918 emptyIfaceDepCache :: Name -> Maybe DeprecTxt
919 emptyIfaceDepCache n = Nothing
920
921 plusDeprecs :: Deprecations -> Deprecations -> Deprecations
922 plusDeprecs d NoDeprecs = d
923 plusDeprecs NoDeprecs d = d
924 plusDeprecs d (DeprecAll t) = DeprecAll t
925 plusDeprecs (DeprecAll t) d = DeprecAll t
926 plusDeprecs (DeprecSome v1) (DeprecSome v2) = DeprecSome (v1 `plusNameEnv` v2)
927 \end{code}
928
929
930 \begin{code}
931 type Avails       = [AvailInfo]
932 type AvailInfo    = GenAvailInfo Name
933 type RdrAvailInfo = GenAvailInfo OccName
934
935 data GenAvailInfo name  = Avail name     -- An ordinary identifier
936                         | AvailTC name   -- The name of the type or class
937                                   [name] -- The available pieces of type/class.
938                                          -- NB: If the type or class is itself
939                                          -- to be in scope, it must be in this list.
940                                          -- Thus, typically: AvailTC Eq [Eq, ==, /=]
941                         deriving( Eq )
942                         -- Equality used when deciding if the interface has changed
943
944 type IfaceExport = (Module, [GenAvailInfo OccName])
945
946 availsToNameSet :: [AvailInfo] -> NameSet
947 availsToNameSet avails = foldr add emptyNameSet avails
948       where add avail set = addListToNameSet set (availNames avail)
949
950 availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
951 availsToNameEnv avails = foldr add emptyNameEnv avails
952      where add avail env = extendNameEnvList env
953                                 (zip (availNames avail) (repeat avail))
954
955 availName :: GenAvailInfo name -> name
956 availName (Avail n)     = n
957 availName (AvailTC n _) = n
958
959 availNames :: GenAvailInfo name -> [name]
960 availNames (Avail n)      = [n]
961 availNames (AvailTC n ns) = ns
962
963 instance Outputable n => Outputable (GenAvailInfo n) where
964    ppr = pprAvail
965
966 pprAvail :: Outputable n => GenAvailInfo n -> SDoc
967 pprAvail (Avail n)      = ppr n
968 pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
969 \end{code}
970
971 \begin{code}
972 mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
973 mkIfaceFixCache pairs 
974   = \n -> lookupOccEnv env n `orElse` defaultFixity
975   where
976    env = mkOccEnv pairs
977
978 emptyIfaceFixCache :: OccName -> Fixity
979 emptyIfaceFixCache n = defaultFixity
980
981 -- This fixity environment is for source code only
982 type FixityEnv = NameEnv FixItem
983
984 -- We keep the OccName in the range so that we can generate an interface from it
985 data FixItem = FixItem OccName Fixity SrcSpan
986
987 instance Outputable FixItem where
988   ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc)
989
990 emptyFixityEnv :: FixityEnv
991 emptyFixityEnv = emptyNameEnv
992
993 lookupFixity :: FixityEnv -> Name -> Fixity
994 lookupFixity env n = case lookupNameEnv env n of
995                         Just (FixItem _ fix _) -> fix
996                         Nothing                -> defaultFixity
997 \end{code}
998
999
1000 %************************************************************************
1001 %*                                                                      *
1002 \subsection{WhatsImported}
1003 %*                                                                      *
1004 %************************************************************************
1005
1006 \begin{code}
1007 type WhetherHasOrphans   = Bool
1008         -- An "orphan" is 
1009         --      * an instance decl in a module other than the defn module for 
1010         --              one of the tycons or classes in the instance head
1011         --      * a transformation rule in a module other than the one defining
1012         --              the function in the head of the rule.
1013
1014 type WhetherHasFamInst = Bool        -- This module defines family instances?
1015
1016 type IsBootInterface = Bool
1017
1018 -- Dependency info about modules and packages below this one
1019 -- in the import hierarchy.  See TcRnTypes.ImportAvails for details.
1020 -- The orphan modules in `dep_orphs' do *not* include family instance orphans,
1021 -- as they are anyway included in `dep_finsts'.
1022 --
1023 -- Invariant: the dependencies of a module M never includes M
1024 -- Invariant: the lists are unordered, with no duplicates
1025 data Dependencies
1026   = Deps { dep_mods   :: [(ModuleName,      -- Home-package module dependencies
1027                            IsBootInterface)]
1028          , dep_pkgs   :: [PackageId]        -- External package dependencies
1029          , dep_orphs  :: [Module]           -- Orphan modules (whether home or
1030                                             -- external pkg)
1031          , dep_finsts :: [Module]           -- Modules that contain family
1032                                             -- instances (whether home or
1033                                             -- external pkg)
1034          }
1035   deriving( Eq )
1036         -- Equality used only for old/new comparison in MkIface.addVersionInfo
1037
1038 noDependencies :: Dependencies
1039 noDependencies = Deps [] [] [] []
1040           
1041 data Usage
1042   = Usage { usg_name     :: ModuleName,                 -- Name of the module
1043             usg_mod      :: Version,                    -- Module version
1044             usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
1045                 -- NB. usages are for parent names only, eg. tycon but not constructors.
1046             usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
1047             usg_rules    :: Version                     -- Orphan-rules version (for non-orphan
1048                                                         -- modules this will always be initialVersion)
1049     }       deriving( Eq )
1050         -- This type doesn't let you say "I imported f but none of the rules in
1051         -- the module". If you use anything in the module you get its rule version
1052         -- So if the rules change, you'll recompile, even if you don't use them.
1053         -- This is easy to implement, and it's safer: you might not have used the rules last
1054         -- time round, but if someone has added a new rule you might need it this time
1055
1056         -- The export list field is (Just v) if we depend on the export list:
1057         --      i.e. we imported the module directly, whether or not we
1058         --           enumerated the things we imported, or just imported everything
1059         -- We need to recompile if M's exports change, because 
1060         -- if the import was    import M,       we might now have a name clash in the 
1061         --                                      importing module.
1062         -- if the import was    import M(x)     M might no longer export x
1063         -- The only way we don't depend on the export list is if we have
1064         --                      import M()
1065         -- And of course, for modules that aren't imported directly we don't
1066         -- depend on their export lists
1067 \end{code}
1068
1069
1070 %************************************************************************
1071 %*                                                                      *
1072                 The External Package State
1073 %*                                                                      *
1074 %************************************************************************
1075
1076 \begin{code}
1077 type PackageTypeEnv    = TypeEnv
1078 type PackageRuleBase   = RuleBase
1079 type PackageInstEnv    = InstEnv
1080 type PackageFamInstEnv = FamInstEnv
1081 type PackageVectInfo   = VectInfo
1082
1083 data ExternalPackageState
1084   = EPS {
1085         eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
1086                 -- In OneShot mode (only), home-package modules
1087                 -- accumulate in the external package state, and are
1088                 -- sucked in lazily.  For these home-pkg modules
1089                 -- (only) we need to record which are boot modules.
1090                 -- We set this field after loading all the
1091                 -- explicitly-imported interfaces, but before doing
1092                 -- anything else
1093                 --
1094                 -- The ModuleName part is not necessary, but it's useful for
1095                 -- debug prints, and it's convenient because this field comes
1096                 -- direct from TcRnTypes.ImportAvails.imp_dep_mods
1097
1098         eps_PIT :: !PackageIfaceTable,
1099                 -- The ModuleIFaces for modules in external packages
1100                 -- whose interfaces we have opened
1101                 -- The declarations in these interface files are held in
1102                 -- eps_decls, eps_inst_env, eps_fam_inst_env, eps_rules
1103                 -- (below), not in the mi_decls fields of the iPIT.  
1104                 -- What _is_ in the iPIT is:
1105                 --      * The Module 
1106                 --      * Version info
1107                 --      * Its exports
1108                 --      * Fixities
1109                 --      * Deprecations
1110
1111         eps_PTE :: !PackageTypeEnv,        -- Domain = external-package modules
1112
1113         eps_inst_env     :: !PackageInstEnv,   -- The total InstEnv accumulated
1114                                                -- from all the external-package
1115                                                -- modules 
1116         eps_fam_inst_env :: !PackageFamInstEnv,-- Ditto FamInstEnv
1117         eps_rule_base    :: !PackageRuleBase,  -- Ditto RuleEnv
1118         eps_vect_info    :: !PackageVectInfo,  -- Ditto VectInfo
1119
1120         eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), -- identifies family
1121                                                        -- instances of each mod 
1122         eps_stats :: !EpsStats
1123   }
1124
1125 -- "In" means read from iface files
1126 -- "Out" means actually sucked in and type-checked
1127 data EpsStats = EpsStats { n_ifaces_in
1128                          , n_decls_in, n_decls_out 
1129                          , n_rules_in, n_rules_out
1130                          , n_insts_in, n_insts_out :: !Int }
1131
1132 addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
1133 -- Add stats for one newly-read interface
1134 addEpsInStats stats n_decls n_insts n_rules
1135   = stats { n_ifaces_in = n_ifaces_in stats + 1
1136           , n_decls_in  = n_decls_in stats + n_decls
1137           , n_insts_in  = n_insts_in stats + n_insts
1138           , n_rules_in  = n_rules_in stats + n_rules }
1139 \end{code}
1140
1141 The NameCache makes sure that there is just one Unique assigned for
1142 each original name; i.e. (module-name, occ-name) pair.  The Name is
1143 always stored as a Global, and has the SrcLoc of its binding location.
1144 Actually that's not quite right.  When we first encounter the original
1145 name, we might not be at its binding site (e.g. we are reading an
1146 interface file); so we give it 'noSrcLoc' then.  Later, when we find
1147 its binding site, we fix it up.
1148
1149 \begin{code}
1150 data NameCache
1151  = NameCache {  nsUniqs :: UniqSupply,
1152                 -- Supply of uniques
1153                 nsNames :: OrigNameCache,
1154                 -- Ensures that one original name gets one unique
1155                 nsIPs   :: OrigIParamCache
1156                 -- Ensures that one implicit parameter name gets one unique
1157    }
1158
1159 type OrigNameCache   = ModuleEnv (OccEnv Name)
1160 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
1161 \end{code}
1162
1163
1164
1165 %************************************************************************
1166 %*                                                                      *
1167                 The module graph and ModSummary type
1168         A ModSummary is a node in the compilation manager's
1169         dependency graph, and it's also passed to hscMain
1170 %*                                                                      *
1171 %************************************************************************
1172
1173 A ModuleGraph contains all the nodes from the home package (only).  
1174 There will be a node for each source module, plus a node for each hi-boot
1175 module.
1176
1177 \begin{code}
1178 type ModuleGraph = [ModSummary]  -- The module graph, 
1179                                  -- NOT NECESSARILY IN TOPOLOGICAL ORDER
1180
1181 emptyMG :: ModuleGraph
1182 emptyMG = []
1183
1184 -- The nodes of the module graph are
1185 --      EITHER a regular Haskell source module
1186 --      OR     a hi-boot source module
1187
1188 data ModSummary
1189    = ModSummary {
1190         ms_mod       :: Module,                 -- Identity of the module
1191         ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
1192         ms_location  :: ModLocation,            -- Location
1193         ms_hs_date   :: ClockTime,              -- Timestamp of source file
1194         ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
1195         ms_srcimps   :: [Located ModuleName],   -- Source imports
1196         ms_imps      :: [Located ModuleName],   -- Non-source imports
1197         ms_hspp_file :: FilePath,               -- Filename of preprocessed source.
1198         ms_hspp_opts :: DynFlags,               -- Cached flags from OPTIONS, INCLUDE
1199                                                 -- and LANGUAGE pragmas.
1200         ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
1201      }
1202
1203 ms_mod_name :: ModSummary -> ModuleName
1204 ms_mod_name = moduleName . ms_mod
1205
1206 -- The ModLocation contains both the original source filename and the
1207 -- filename of the cleaned-up source file after all preprocessing has been
1208 -- done.  The point is that the summariser will have to cpp/unlit/whatever
1209 -- all files anyway, and there's no point in doing this twice -- just 
1210 -- park the result in a temp file, put the name of it in the location,
1211 -- and let @compile@ read from that file on the way back up.
1212
1213 -- The ModLocation is stable over successive up-sweeps in GHCi, wheres
1214 -- the ms_hs_date and imports can, of course, change
1215
1216 msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
1217 msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
1218 msHiFilePath  ms = ml_hi_file  (ms_location ms)
1219 msObjFilePath ms = ml_obj_file (ms_location ms)
1220
1221 isBootSummary :: ModSummary -> Bool
1222 isBootSummary ms = isHsBoot (ms_hsc_src ms)
1223
1224 instance Outputable ModSummary where
1225    ppr ms
1226       = sep [text "ModSummary {",
1227              nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
1228                           text "ms_mod =" <+> ppr (ms_mod ms) 
1229                                 <> text (hscSourceString (ms_hsc_src ms)) <> comma,
1230                           text "ms_imps =" <+> ppr (ms_imps ms),
1231                           text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
1232              char '}'
1233             ]
1234
1235 showModMsg :: HscTarget -> Bool -> ModSummary -> String
1236 showModMsg target recomp mod_summary
1237   = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
1238                     char '(', text (msHsFilePath mod_summary) <> comma,
1239                     case target of
1240                       HscInterpreted | recomp 
1241                                  -> text "interpreted"
1242                       HscNothing -> text "nothing"
1243                       _other     -> text (msObjFilePath mod_summary),
1244                     char ')'])
1245  where 
1246     mod     = moduleName (ms_mod mod_summary)
1247     mod_str = showSDoc (ppr mod) ++ hscSourceString (ms_hsc_src mod_summary)
1248 \end{code}
1249
1250
1251 %************************************************************************
1252 %*                                                                      *
1253 \subsection{Hpc Support}
1254 %*                                                                      *
1255 %************************************************************************
1256
1257 \begin{code}
1258 data HpcInfo = HpcInfo 
1259      { hpcInfoTickCount :: Int 
1260      , hpcInfoHash      :: Int  
1261      }
1262      | NoHpcInfo
1263
1264 noHpcInfo :: HpcInfo
1265 noHpcInfo = NoHpcInfo
1266 \end{code}
1267
1268 %************************************************************************
1269 %*                                                                      *
1270 \subsection{Vectorisation Support}
1271 %*                                                                      *
1272 %************************************************************************
1273
1274 The following information is generated and consumed by the vectorisation
1275 subsystem.  It communicates the vectorisation status of declarations from one
1276 module to another.
1277
1278 Why do we need both f and f_v in the ModGuts/ModDetails/EPS version VectInfo
1279 below?  We need to know `f' when converting to IfaceVectInfo.  However, during
1280 vectorisation, we need to know `f_v', whose `Var' we cannot lookup based
1281 on just the OccName easily in a Core pass.
1282
1283 \begin{code}
1284 -- ModGuts/ModDetails/EPS version
1285 data VectInfo      
1286   = VectInfo {
1287       vectInfoVar     :: VarEnv  (Var    , Var  ),   -- (f, f_v) keyed on f
1288       vectInfoTyCon   :: NameEnv (TyCon  , TyCon),   -- (T, T_v) keyed on T
1289       vectInfoDataCon :: NameEnv (DataCon, DataCon), -- (C, C_v) keyed on C
1290       vectInfoIso     :: NameEnv (TyCon  , Var)      -- (T, isoT) keyed on T
1291     }
1292     -- all of this is always tidy, even in ModGuts
1293
1294 -- ModIface version
1295 data IfaceVectInfo 
1296   = IfaceVectInfo {
1297       ifaceVectInfoVar        :: [Name],
1298         -- all variables in here have a vectorised variant;
1299         -- the name of the vectorised variant is determined by `mkCloVect'
1300       ifaceVectInfoTyCon      :: [Name],
1301         -- all tycons in here have a vectorised variant;
1302         -- the name of the vectorised variant and those of its
1303         -- data constructors are determined by `mkVectTyConOcc'
1304         -- and `mkVectDataConOcc'; the names of
1305         -- the isomorphisms is determined by `mkVectIsoOcc'
1306       ifaceVectInfoTyConReuse :: [Name]              
1307         -- the vectorised form of all the tycons in here coincids with
1308         -- the unconverted from; the names of the isomorphisms is determined
1309         -- by `mkVectIsoOcc'
1310     }
1311
1312 noVectInfo :: VectInfo
1313 noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv
1314
1315 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
1316 plusVectInfo vi1 vi2 = 
1317   VectInfo (vectInfoVar     vi1 `plusVarEnv`  vectInfoVar     vi2)
1318            (vectInfoTyCon   vi1 `plusNameEnv` vectInfoTyCon   vi2)
1319            (vectInfoDataCon vi1 `plusNameEnv` vectInfoDataCon vi2)
1320            (vectInfoIso     vi1 `plusNameEnv` vectInfoIso     vi2)
1321
1322 noIfaceVectInfo :: IfaceVectInfo
1323 noIfaceVectInfo = IfaceVectInfo [] [] []
1324 \end{code}
1325
1326 %************************************************************************
1327 %*                                                                      *
1328 \subsection{Linkable stuff}
1329 %*                                                                      *
1330 %************************************************************************
1331
1332 This stuff is in here, rather than (say) in Linker.lhs, because the Linker.lhs
1333 stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
1334
1335 \begin{code}
1336 data Linkable = LM {
1337   linkableTime     :: ClockTime,        -- Time at which this linkable was built
1338                                         -- (i.e. when the bytecodes were produced,
1339                                         --       or the mod date on the files)
1340   linkableModule   :: Module,           -- Should be Module, but see below
1341   linkableUnlinked :: [Unlinked]
1342  }
1343
1344 isObjectLinkable :: Linkable -> Bool
1345 isObjectLinkable l = not (null unlinked) && all isObject unlinked
1346   where unlinked = linkableUnlinked l
1347         -- A linkable with no Unlinked's is treated as a BCO.  We can
1348         -- generate a linkable with no Unlinked's as a result of
1349         -- compiling a module in HscNothing mode, and this choice
1350         -- happens to work well with checkStability in module GHC.
1351
1352 instance Outputable Linkable where
1353    ppr (LM when_made mod unlinkeds)
1354       = (text "LinkableM" <+> parens (text (show when_made)) <+> ppr mod)
1355         $$ nest 3 (ppr unlinkeds)
1356
1357 -------------------------------------------
1358 data Unlinked
1359    = DotO FilePath
1360    | DotA FilePath
1361    | DotDLL FilePath
1362    | BCOs CompiledByteCode
1363
1364 #ifndef GHCI
1365 data CompiledByteCode = NoByteCode
1366 #endif
1367
1368 instance Outputable Unlinked where
1369    ppr (DotO path)   = text "DotO" <+> text path
1370    ppr (DotA path)   = text "DotA" <+> text path
1371    ppr (DotDLL path) = text "DotDLL" <+> text path
1372 #ifdef GHCI
1373    ppr (BCOs bcos)   = text "BCOs" <+> ppr bcos
1374 #else
1375    ppr (BCOs bcos)   = text "No byte code"
1376 #endif
1377
1378 isObject (DotO _)   = True
1379 isObject (DotA _)   = True
1380 isObject (DotDLL _) = True
1381 isObject _          = False
1382
1383 isInterpretable = not . isObject
1384
1385 nameOfObject (DotO fn)   = fn
1386 nameOfObject (DotA fn)   = fn
1387 nameOfObject (DotDLL fn) = fn
1388 nameOfObject other       = pprPanic "nameOfObject" (ppr other)
1389
1390 byteCodeOfObject (BCOs bc) = bc
1391 byteCodeOfObject other     = pprPanic "byteCodeOfObject" (ppr other)
1392 \end{code}
1393
1394 %************************************************************************
1395 %*                                                                      *
1396 \subsection{Breakpoint Support}
1397 %*                                                                      *
1398 %************************************************************************
1399
1400 \begin{code}
1401 type BreakIndex = Int
1402
1403 -- | all the information about the breakpoints for a given module
1404 data ModBreaks
1405    = ModBreaks
1406    { modBreaks_flags :: BreakArray
1407         -- The array of flags, one per breakpoint, 
1408         -- indicating which breakpoints are enabled.
1409    , modBreaks_locs :: !(Array BreakIndex SrcSpan)
1410         -- An array giving the source span of each breakpoint.
1411    , modBreaks_vars :: !(Array BreakIndex [OccName])
1412         -- An array giving the names of the free variables at each breakpoint.
1413    }
1414
1415 emptyModBreaks :: ModBreaks
1416 emptyModBreaks = ModBreaks
1417    { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
1418          -- Todo: can we avoid this? 
1419    , modBreaks_locs = array (0,-1) []
1420    , modBreaks_vars = array (0,-1) []
1421    }
1422 \end{code}