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