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