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