fix for compiling the base package with --make
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
index bcb967f..00e1b49 100644 (file)
@@ -5,24 +5,32 @@
 
 \begin{code}
 module HscTypes ( 
-       HscEnv(..), hscEPS,
-       GhciMode(..), isOneShot,
+       -- * Sessions and compilation state
+       Session(..), HscEnv(..), hscEPS,
+       FinderCache, FinderCacheEntry,
+       Target(..), TargetId(..), pprTarget, pprTargetId,
+       ModuleGraph, emptyMG,
 
-       ModDetails(..), 
-       ModGuts(..), ModImports(..), ForeignStubs(..),
+       ModDetails(..), emptyModDetails,
+       ModGuts(..), CgGuts(..), ModImports(..), ForeignStubs(..),
 
+       ModSummary(..), showModMsg, isBootSummary,
+       msHsFilePath, msHiFilePath, msObjFilePath, 
+
+       HscSource(..), isHsBoot, hscSourceString,       -- Re-exported from DriverPhases
+       
        HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
+       hptInstances, hptRules,
 
        ExternalPackageState(..), EpsStats(..), addEpsInStats,
        PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
-       lookupIface, lookupIfaceByModName, moduleNameToModule,
-       emptyModIface,
+       lookupIface, lookupIfaceByModule, emptyModIface,
 
        InteractiveContext(..), emptyInteractiveContext, 
        icPrintUnqual, unQualInScope,
 
        ModIface(..), mkIfaceDepCache, mkIfaceVerCache, mkIfaceFixCache,
-                     emptyIfaceDepCache, 
+       emptyIfaceDepCache, 
 
        Deprecs(..), IfaceDeprecs,
 
@@ -37,8 +45,6 @@ module HscTypes (
 
        WhetherHasOrphans, IsBootInterface, Usage(..), 
        Dependencies(..), noDependencies,
-       InstPool, Gated, addInstsToPool, 
-       RulePool, addRulesToPool, 
        NameCache(..), OrigNameCache, OrigIParamCache,
        Avails, availsToNameSet, availName, availNames,
        GenAvailInfo(..), AvailInfo, RdrAvailInfo, 
@@ -46,7 +52,6 @@ module HscTypes (
 
        Deprecations, DeprecTxt, lookupDeprec, plusDeprecs,
 
-       InstEnv, DFunId,
        PackageInstEnv, PackageRuleBase,
 
        -- Linker stuff
@@ -64,13 +69,13 @@ import ByteCodeAsm  ( CompiledByteCode )
 import RdrName         ( GlobalRdrEnv, emptyGlobalRdrEnv,
                          LocalRdrEnv, emptyLocalRdrEnv,
                          GlobalRdrElt(..), mkRdrUnqual, lookupGRE_RdrName )
-import Name            ( Name, NamedThing, getName, nameOccName, nameModule, nameModuleName )
+import Name            ( Name, NamedThing, getName, nameOccName, nameModule )
 import NameEnv
 import NameSet 
 import OccName         ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, 
                          extendOccEnv )
 import Module
-import InstEnv         ( InstEnv, DFunId )
+import InstEnv         ( InstEnv, Instance )
 import Rules           ( RuleBase )
 import CoreSyn         ( CoreBind )
 import Id              ( Id )
@@ -79,24 +84,25 @@ import Type         ( TyThing(..) )
 import Class           ( Class, classSelIds, classTyCon )
 import TyCon           ( TyCon, tyConSelIds, tyConDataCons )
 import DataCon         ( dataConImplicitIds )
-import Packages                ( PackageName )
-import CmdLineOpts     ( DynFlags )
-
+import PrelNames       ( gHC_PRIM )
+import Packages                ( PackageIdH, PackageId, PackageConfig, HomeModules )
+import DynFlags                ( DynFlags(..), isOneShot )
+import DriverPhases    ( HscSource(..), isHsBoot, hscSourceString, Phase )
 import BasicTypes      ( Version, initialVersion, IPName, 
                          Fixity, defaultFixity, DeprecTxt )
 
 import IfaceSyn                ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
 
 import FiniteMap       ( FiniteMap )
-import CoreSyn         ( IdCoreRule )
-import Maybes          ( orElse )
+import CoreSyn         ( CoreRule )
+import Maybes          ( orElse, expectJust, expectJust )
 import Outputable
-import SrcLoc          ( SrcSpan )
+import SrcLoc          ( SrcSpan, Located )
 import UniqSupply      ( UniqSupply )
-import Maybe           ( fromJust )
 import FastString      ( FastString )
 
 import DATA_IOREF      ( IORef, readIORef )
+import StringBuffer    ( StringBuffer )
 import Time            ( ClockTime )
 \end{code}
 
@@ -107,14 +113,42 @@ import Time               ( ClockTime )
 %*                                                                     *
 %************************************************************************
 
-The HscEnv gives the environment in which to compile a chunk of code.
+
+\begin{code}
+-- | The Session is a handle to the complete state of a compilation
+-- session.  A compilation session consists of a set of modules
+-- constituting the current program or library, the context for
+-- interactive evaluation, and various caches.
+newtype Session = Session (IORef HscEnv)
+\end{code}
+
+HscEnv is like Session, except that some of the fields are immutable.
+An HscEnv is used to compile a single module from plain Haskell source
+code (after preprocessing) to either C, assembly or C--.  Things like
+the module graph don't change during a single compilation.
+
+Historical note: "hsc" used to be the name of the compiler binary,
+when there was a separate driver and compiler.  To compile a single
+module, the driver would invoke hsc on the source code... so nowadays
+we think of hsc as the layer of the compiler that deals with compiling
+a single module.
 
 \begin{code}
 data HscEnv 
-  = HscEnv { hsc_mode   :: GhciMode,
-            hsc_dflags :: DynFlags,
+  = HscEnv { 
+       hsc_dflags :: DynFlags,
+               -- The dynamic flag settings
 
-            hsc_HPT    :: HomePackageTable,
+       hsc_targets :: [Target],
+               -- The targets (or roots) of the current session
+
+       hsc_mod_graph :: ModuleGraph,
+               -- The module graph of the current session
+
+       hsc_IC :: InteractiveContext,
+               -- The context for evaluating interactive statements
+
+       hsc_HPT    :: HomePackageTable,
                -- The home package table describes already-compiled
                -- home-packge modules, *excluding* the module we 
                -- are compiling right now.
@@ -127,43 +161,75 @@ data HscEnv
                -- hsc_HPT is not mutable because we only demand-load 
                -- external packages; the home package is eagerly 
                -- loaded, module by module, by the compilation manager.
+               --      
+               -- The HPT may contain modules compiled earlier by --make
+               -- but not actually below the current module in the dependency
+               -- graph.  (This changes a previous invariant: changed Jan 05.)
        
-               -- The next two are side-effected by compiling
-               -- to reflect sucking in interface files
-            hsc_EPS    :: IORef ExternalPackageState,
-            hsc_NC     :: IORef NameCache }
+       hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
+       hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
+               -- These are side-effected by compiling to reflect
+               -- sucking in interface files.  They cache the state of
+               -- external interface files, in effect.
+
+       hsc_FC  :: {-# UNPACK #-} !(IORef FinderCache)
+               -- The finder's cache.  This caches the location of modules,
+               -- so we don't have to search the filesystem multiple times.
+ }
 
 hscEPS :: HscEnv -> IO ExternalPackageState
 hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
-\end{code}
-
-The GhciMode is self-explanatory:
-
-\begin{code}
-data GhciMode = Batch          -- ghc --make Main
-             | Interactive     -- ghc --interactive
-             | OneShot         -- ghc Foo.hs
-             | IDE             -- Visual Studio etc
-             deriving Eq
-
-isOneShot :: GhciMode -> Bool
-isOneShot OneShot = True
-isOneShot _other  = False
-\end{code}
 
-\begin{code}
-type HomePackageTable  = ModuleEnv HomeModInfo -- Domain = modules in the home package
-type PackageIfaceTable = ModuleEnv ModIface    -- Domain = modules in the imported packages
+-- | A compilation target.
+--
+-- A target may be supplied with the actual text of the
+-- module.  If so, use this instead of the file contents (this
+-- is for use in an IDE where the file hasn't been saved by
+-- the user yet).
+data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
+
+data TargetId
+  = TargetModule Module
+       -- ^ A module name: search for the file
+  | TargetFile FilePath (Maybe Phase)
+       -- ^ A filename: preprocess & parse it to find the module name.
+       -- If specified, the Phase indicates how to compile this file
+       -- (which phase to start from).  Nothing indicates the starting phase
+       -- should be determined from the suffix of the filename.
+  deriving Eq
+
+pprTarget :: Target -> SDoc
+pprTarget (Target id _) = pprTargetId id
+
+pprTargetId (TargetModule m) = ppr m
+pprTargetId (TargetFile f _) = text f
+
+type FinderCache = ModuleEnv FinderCacheEntry
+type FinderCacheEntry = (ModLocation, Maybe (PackageConfig,Bool))
+       -- The finder's cache (see module Finder)
+
+type HomePackageTable  = ModuleEnv HomeModInfo
+       -- Domain = modules in the home package
+type PackageIfaceTable = ModuleEnv ModIface
+       -- Domain = modules in the imported packages
 
 emptyHomePackageTable  = emptyModuleEnv
 emptyPackageIfaceTable = emptyModuleEnv
 
 data HomeModInfo 
-  = HomeModInfo { hm_iface    :: ModIface,
-                 hm_globals  :: Maybe GlobalRdrEnv,    -- Its top level environment
-                                                       -- Nothing <-> compiled module
-                 hm_details  :: ModDetails,
-                 hm_linkable :: Linkable }
+  = HomeModInfo { hm_iface    :: !ModIface,
+                 hm_details  :: !ModDetails,
+                 hm_linkable :: !(Maybe Linkable) }
+               -- hm_linkable might be Nothing if:
+               --   a) this is an .hs-boot module
+               --   b) temporarily during compilation if we pruned away
+               --      the old linkable because it was out of date.
+               -- after a complete compilation (GHC.load), all hm_linkable
+               -- fields in the HPT will be Just.
+               --
+               -- When re-linking a module (hscNoRecomp), we construct
+               -- the HomModInfo by building a new ModDetails from the
+               -- old ModIface (only).
 \end{code}
 
 Simple lookups in the symbol table.
@@ -176,21 +242,54 @@ lookupIface hpt pit mod
        Just mod_info -> Just (hm_iface mod_info)
        Nothing       -> lookupModuleEnv pit mod
 
-lookupIfaceByModName :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Maybe ModIface
+lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
 -- We often have two IfaceTables, and want to do a lookup
-lookupIfaceByModName hpt pit mod
-  = case lookupModuleEnvByName hpt mod of
+lookupIfaceByModule hpt pit mod
+  = case lookupModuleEnv hpt mod of
        Just mod_info -> Just (hm_iface mod_info)
-       Nothing       -> lookupModuleEnvByName pit mod
+       Nothing       -> lookupModuleEnv pit mod
 \end{code}
 
+
 \begin{code}
--- Use instead of Finder.findModule if possible: this way doesn't
--- require filesystem operations, and it is guaranteed not to fail
--- when the IfaceTables are properly populated (i.e. after the renamer).
-moduleNameToModule :: HomePackageTable -> PackageIfaceTable -> ModuleName -> Module
-moduleNameToModule hpt pit mod 
-   = mi_module (fromJust (lookupIfaceByModName hpt pit mod))
+hptInstances :: HscEnv -> (Module -> Bool) -> [Instance]
+-- Find all the instance declarations that are in modules imported 
+-- by this one, directly or indirectly, and are in the Home Package Table
+-- This ensures that we don't see instances from modules --make compiled 
+-- before this one, but which are not below this one
+hptInstances hsc_env want_this_module
+  = [ ispec 
+    | mod_info <- moduleEnvElts (hsc_HPT hsc_env)
+    , want_this_module (mi_module (hm_iface mod_info))
+    , ispec <- md_insts (hm_details mod_info) ]
+
+hptRules :: HscEnv -> [(Module, IsBootInterface)] -> [CoreRule]
+-- Get rules from modules "below" this one (in the dependency sense)
+-- C.f Inst.hptInstances
+hptRules hsc_env deps
+  | isOneShot (ghcMode (hsc_dflags hsc_env)) = []
+  | otherwise
+  = let 
+       hpt = hsc_HPT hsc_env
+    in
+    [ rule
+    |  -- Find each non-hi-boot module below me
+      (mod, False) <- deps
+
+       -- unsavoury: when compiling the base package with --make, we
+       -- sometimes try to look up RULES for GHC.Prim.  GHC.Prim won't
+       -- be in the HPT, because we never compile it; it's in the EPT
+       -- instead.  ToDo: clean up, and remove this slightly bogus
+       -- filter:
+    , mod /= gHC_PRIM
+
+       -- Look it up in the HPT
+    , let mod_info = case lookupModuleEnv hpt mod of
+                       Nothing -> pprPanic "hptRules" (ppr mod <+> ppr deps)
+                       Just x  -> x
+
+       -- And get its dfuns
+    , rule <- md_rules (hm_details mod_info) ]
 \end{code}
 
 
@@ -212,7 +311,7 @@ the declarations into a single indexed map in the @PersistentRenamerState@.
 \begin{code}
 data ModIface 
    = ModIface {
-       mi_package  :: !PackageName,        -- Which package the module comes from
+       mi_package  :: !PackageIdH,         -- Which package the module comes from
         mi_module   :: !Module,
         mi_mod_vers :: !Version,           -- Module version: changes when anything changes
 
@@ -250,6 +349,21 @@ data ModIface
                -- the version of the parent class/tycon changes
        mi_decls :: [(Version,IfaceDecl)],      -- Sorted
 
+        mi_globals  :: !(Maybe GlobalRdrEnv),
+               -- Binds all the things defined at the top level in
+               -- the *original source* code for this module. which
+               -- is NOT the same as mi_exports, nor mi_decls (which
+               -- may contains declarations for things not actually
+               -- defined by the user).  Used for GHCi and for inspecting
+               -- the contents of modules via the GHC API only.
+               --
+               -- (We need the source file to figure out the
+               -- top-level environment, if we didn't compile this module
+               -- from source then this field contains Nothing).
+               --
+               -- Strictly speaking this field should live in the
+               -- HomeModInfo, but that leads to more plumbing.
+
                -- Instance declarations and rules
        mi_insts     :: [IfaceInst],    -- Sorted
        mi_rules     :: [IfaceRule],    -- Sorted
@@ -270,11 +384,17 @@ data ModIface
 data ModDetails
    = ModDetails {
        -- The next three fields are created by the typechecker
+       md_exports  :: NameSet,
         md_types    :: !TypeEnv,
-        md_insts    :: ![DFunId],      -- Dfun-ids for the instances in this module
-        md_rules    :: ![IdCoreRule]   -- Domain may include Ids from other modules
+        md_insts    :: ![Instance],    -- Dfun-ids for the instances in this module
+        md_rules    :: ![CoreRule]     -- Domain may include Ids from other modules
      }
 
+emptyModDetails = ModDetails { md_types = emptyTypeEnv,
+                              md_exports = emptyNameSet,
+                              md_insts = [],
+                              md_rules = [] }
+
 -- A ModGuts is carried through the compiler, accumulating stuff as it goes
 -- There is only one ModGuts at any time, the one for the module
 -- being compiled right now.  Once it is compiled, a ModIface and 
@@ -283,8 +403,10 @@ data ModDetails
 data ModGuts
   = ModGuts {
         mg_module   :: !Module,
+       mg_boot     :: IsBootInterface, -- Whether it's an hs-boot module
        mg_exports  :: !NameSet,        -- What it exports
        mg_deps     :: !Dependencies,   -- What is below it, directly or otherwise
+       mg_home_mods :: !HomeModules,   -- For calling isHomeModule etc.
        mg_dir_imps :: ![Module],       -- Directly-imported modules; used to
                                        --      generate initialisation code
        mg_usages   :: ![Usage],        -- Version info for what it needed
@@ -294,8 +416,8 @@ data ModGuts
        mg_deprecs  :: !Deprecations,   -- Deprecations declared in the module
 
        mg_types    :: !TypeEnv,
-       mg_insts    :: ![DFunId],       -- Instances 
-        mg_rules    :: ![IdCoreRule],  -- Rules from this module
+       mg_insts    :: ![Instance],     -- Instances 
+        mg_rules    :: ![CoreRule],    -- Rules from this module
        mg_binds    :: ![CoreBind],     -- Bindings for this module
        mg_foreign  :: !ForeignStubs
     }
@@ -305,24 +427,40 @@ data ModGuts
 -- After simplification, the following fields change slightly:
 --     mg_rules        Orphan rules only (local ones now attached to binds)
 --     mg_binds        With rules attached
---
--- After CoreTidy, the following fields change slightly:
---     mg_types        Now contains Ids as well, replete with final IdInfo
---                        The Ids are only the ones that are visible from
---                        importing modules.  Without -O that means only
---                        exported Ids, but with -O importing modules may
---                        see ids mentioned in unfoldings of exported Ids
---
---     mg_insts        Same DFunIds as before, but with final IdInfo,
---                        and the unique might have changed; remember that
---                        CoreTidy links up the uniques of old and new versions
---
---     mg_rules        All rules for exported things, substituted with final Ids
---
---     mg_binds        Tidied
 
 
+---------------------------------------------------------
+-- The Tidy pass forks the information about this module: 
+--     * one lot goes to interface file generation (ModIface)
+--       and later compilations (ModDetails)
+--     * the other lot goes to code generation (CgGuts)
+data CgGuts 
+  = CgGuts {
+       cg_module   :: !Module,
+
+       cg_tycons   :: [TyCon],
+               -- Algebraic data types (including ones that started
+               -- life as classes); generate constructors and info
+               -- tables Includes newtypes, just for the benefit of
+               -- External Core
+
+       cg_binds    :: [CoreBind],
+               -- The tidied main bindings, including
+               -- previously-implicit bindings for record and class
+               -- selectors, and data construtor wrappers.  But *not*
+               -- data constructor workers; reason: we we regard them
+               -- as part of the code-gen of tycons
+
+       cg_dir_imps :: ![Module],
+               -- Directly-imported modules; used to generate
+               -- initialisation code
+
+       cg_foreign  :: !ForeignStubs,   
+       cg_home_mods :: !HomeModules,   -- for calling isHomeModule etc.
+       cg_dep_pkgs :: ![PackageId]     -- Used to generate #includes for C code gen
+    }
 
+-----------------------------------
 data ModImports
   = ModImports {
        imp_direct     :: ![(Module,Bool)],     -- Explicitly-imported modules
@@ -334,6 +472,7 @@ data ModImports
                                                --      directly or indirectly
     }
 
+-----------------------------------
 data ForeignStubs = NoStubs
                  | ForeignStubs
                        SDoc            -- Header file prototypes for
@@ -348,10 +487,10 @@ data ForeignStubs = NoStubs
 \end{code}
 
 \begin{code}
-emptyModIface :: PackageName -> ModuleName -> ModIface
+emptyModIface :: PackageIdH -> Module -> ModIface
 emptyModIface pkg mod
   = ModIface { mi_package  = pkg,
-              mi_module   = mkModule pkg mod,
+              mi_module   = mod,
               mi_mod_vers = initialVersion,
               mi_orphan   = False,
               mi_boot     = False,
@@ -364,6 +503,7 @@ emptyModIface pkg mod
               mi_insts = [],
               mi_rules = [],
               mi_decls = [],
+              mi_globals  = Nothing,
               mi_rule_vers = initialVersion,
               mi_dep_fn = emptyIfaceDepCache,
               mi_fix_fn = emptyIfaceFixCache,
@@ -381,10 +521,10 @@ emptyModIface pkg mod
 \begin{code}
 data InteractiveContext 
   = InteractiveContext { 
-       ic_toplev_scope :: [String],    -- Include the "top-level" scope of
+       ic_toplev_scope :: [Module],    -- Include the "top-level" scope of
                                        -- these modules
 
-       ic_exports :: [String],         -- Include just the exports of these
+       ic_exports :: [Module],         -- Include just the exports of these
                                        -- modules
 
        ic_rn_gbl_env :: GlobalRdrEnv,  -- The cached GlobalRdrEnv, built from
@@ -421,7 +561,7 @@ unQualInScope :: GlobalRdrEnv -> PrintUnqualified
 -- [Out of date] Also checks for built-in syntax, which is always 'in scope'
 unQualInScope env mod occ
   = case lookupGRE_RdrName (mkRdrUnqual occ) env of
-       [gre] -> nameModuleName (gre_name gre) == mod
+       [gre] -> nameModule (gre_name gre) == mod
        other -> False
 \end{code}
 
@@ -546,6 +686,11 @@ data Deprecs a
 
 type IfaceDeprecs = Deprecs [(OccName,DeprecTxt)]
 type Deprecations = Deprecs (NameEnv (OccName,DeprecTxt))
+       -- Keep the OccName so we can flatten the NameEnv to
+       -- get an IfaceDeprecs from a Deprecations
+       -- Only an OccName is needed, because a deprecation always
+       -- applies to things defined in the module in which the
+       -- deprecation appears.
 
 mkIfaceDepCache:: IfaceDeprecs -> Name -> Maybe DeprecTxt
 mkIfaceDepCache NoDeprecs        = \n -> Nothing
@@ -585,7 +730,7 @@ data GenAvailInfo name      = Avail name     -- An ordinary identifier
                        deriving( Eq )
                        -- Equality used when deciding if the interface has changed
 
-type IfaceExport = (ModuleName, [GenAvailInfo OccName])
+type IfaceExport = (Module, [GenAvailInfo OccName])
 
 availsToNameSet :: [AvailInfo] -> NameSet
 availsToNameSet avails = foldl add emptyNameSet avails
@@ -662,9 +807,9 @@ type IsBootInterface = Bool
 -- Invariant: the dependencies of a module M never includes M
 -- Invariant: the lists are unordered, with no duplicates
 data Dependencies
-  = Deps { dep_mods  :: [(ModuleName,IsBootInterface)],        -- Home-package module dependencies
-          dep_pkgs  :: [PackageName],                  -- External package dependencies
-          dep_orphs :: [ModuleName] }                  -- Orphan modules (whether home or external pkg)
+  = Deps { dep_mods  :: [(Module,IsBootInterface)],    -- Home-package module dependencies
+          dep_pkgs  :: [PackageId],                    -- External package dependencies
+          dep_orphs :: [Module] }                      -- Orphan modules (whether home or external pkg)
   deriving( Eq )
        -- Equality used only for old/new comparison in MkIface.addVersionInfo
 
@@ -672,7 +817,7 @@ noDependencies :: Dependencies
 noDependencies = Deps [] [] []
          
 data Usage
-  = Usage { usg_name     :: ModuleName,                        -- Name of the module
+  = Usage { usg_name     :: Module,                    -- Name of the module
            usg_mod      :: Version,                    -- Module version
            usg_entities :: [(OccName,Version)],        -- Sorted by occurrence name
            usg_exports  :: Maybe Version,              -- Export-list version, if we depend on it
@@ -686,9 +831,16 @@ data Usage
        -- time round, but if someone has added a new rule you might need it this time
 
        -- The export list field is (Just v) if we depend on the export list:
-       --      i.e. we imported the module without saying exactly what we imported
-       -- We need to recompile if the module exports changes, because we might
-       -- now have a name clash in the importing module.
+       --      i.e. we imported the module directly, whether or not we
+       --           enumerated the things we imported, or just imported everything
+       -- We need to recompile if M's exports change, because 
+       -- if the import was    import M,       we might now have a name clash in the 
+       --                                      importing module.
+       -- if the import was    import M(x)     M might no longer export x
+       -- The only way we don't depend on the export list is if we have
+       --                      import M()
+       -- And of course, for modules that aren't imported directly we don't
+       -- depend on their export lists
 \end{code}
 
 
@@ -705,14 +857,14 @@ type PackageInstEnv  = InstEnv
 
 data ExternalPackageState
   = EPS {
-       eps_is_boot :: !(ModuleEnv (ModuleName, IsBootInterface)),
+       eps_is_boot :: !(ModuleEnv (Module, IsBootInterface)),
                -- In OneShot mode (only), home-package modules accumulate in the
                -- external package state, and are sucked in lazily.
                -- For these home-pkg modules (only) we need to record which are
                -- boot modules.  We set this field after loading all the 
                -- explicitly-imported interfaces, but before doing anything else
                --
-               -- The ModuleName part is not necessary, but it's useful for
+               -- The Module part is not necessary, but it's useful for
                -- debug prints, and it's convenient because this field comes
                -- direct from TcRnTypes.ImportAvails.imp_dep_mods
 
@@ -720,7 +872,7 @@ data ExternalPackageState
                -- The ModuleIFaces for modules in external packages
                -- whose interfaces we have opened
                -- The declarations in these interface files are held in
-               -- eps_decls, eps_insts, eps_rules (below), not in the 
+               -- eps_decls, eps_inst_env, eps_rules (below), not in the 
                -- mi_decls fields of the iPIT.  
                -- What _is_ in the iPIT is:
                --      * The Module 
@@ -735,18 +887,6 @@ data ExternalPackageState
                                                --   all the external-package modules
        eps_rule_base :: !PackageRuleBase,      -- Ditto RuleEnv
 
-
-       -- Holding pens for stuff that has been read in from file,
-       -- but not yet slurped into the renamer
-       eps_insts :: !InstPool,
-               -- The as-yet un-slurped instance decls
-               -- Decls move from here to eps_inst_env
-               -- Each instance is 'gated' by the names that must be 
-               -- available before this instance decl is needed.
-
-       eps_rules :: !RulePool,
-               -- The as-yet un-slurped rules
-
        eps_stats :: !EpsStats
   }
 
@@ -756,6 +896,14 @@ data EpsStats = EpsStats { n_ifaces_in
                         , n_decls_in, n_decls_out 
                         , n_rules_in, n_rules_out
                         , n_insts_in, n_insts_out :: !Int }
+
+addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
+-- Add stats for one newly-read interface
+addEpsInStats stats n_decls n_insts n_rules
+  = stats { n_ifaces_in = n_ifaces_in stats + 1
+         , n_decls_in  = n_decls_in stats + n_decls
+         , n_insts_in  = n_insts_in stats + n_insts
+         , n_rules_in  = n_rules_in stats + n_rules }
 \end{code}
 
 The NameCache makes sure that there is just one Unique assigned for
@@ -766,10 +914,6 @@ name, we might not be at its binding site (e.g. we are reading an
 interface file); so we give it 'noSrcLoc' then.  Later, when we find
 its binding site, we fix it up.
 
-Exactly the same is true of the Module stored in the Name.  When we first
-encounter the occurrence, we may not know the details of the module, so
-we just store junk.  Then when we find the binding site, we fix it up.
-
 \begin{code}
 data NameCache
  = NameCache {  nsUniqs :: UniqSupply,
@@ -784,45 +928,84 @@ type OrigNameCache   = ModuleEnv (OccEnv Name)
 type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
 \end{code}
 
-\begin{code}
-type Gated d = ([Name], (ModuleName, d))       -- The [Name] 'gate' the declaration; always non-empty
-                                               -- ModuleName records which iface file this
-                                               -- decl came from
-
-type RulePool = [Gated IfaceRule]
 
-addRulesToPool :: RulePool
-             -> [Gated IfaceRule]
-             -> RulePool
-addRulesToPool rules new_rules = new_rules ++ rules
 
--------------------------
-addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
--- Add stats for one newly-read interface
-addEpsInStats stats n_decls n_insts n_rules
-  = stats { n_ifaces_in = n_ifaces_in stats + 1
-         , n_decls_in  = n_decls_in stats + n_decls
-         , n_insts_in  = n_insts_in stats + n_insts
-         , n_rules_in  = n_rules_in stats + n_rules }
+%************************************************************************
+%*                                                                     *
+               The module graph and ModSummary type
+       A ModSummary is a node in the compilation manager's
+       dependency graph, and it's also passed to hscMain
+%*                                                                     *
+%************************************************************************
 
--------------------------
-type InstPool = NameEnv [Gated IfaceInst]
-       -- The key of the Pool is the Class
-       -- The Names are the TyCons in the instance head
-       -- For example, suppose this is in an interface file
-       --      instance C T where ...
-       -- We want to slurp this decl if both C and T are "visible" in 
-       -- the importing module.  See "The gating story" in RnIfaces for details.
+A ModuleGraph contains all the nodes from the home package (only).  
+There will be a node for each source module, plus a node for each hi-boot
+module.
 
+\begin{code}
+type ModuleGraph = [ModSummary]  -- The module graph, 
+                                -- NOT NECESSARILY IN TOPOLOGICAL ORDER
+
+emptyMG :: ModuleGraph
+emptyMG = []
+
+-- The nodes of the module graph are
+--     EITHER a regular Haskell source module
+--     OR     a hi-boot source module
+
+data ModSummary
+   = ModSummary {
+        ms_mod       :: Module,                        -- Name of the module
+       ms_hsc_src   :: HscSource,              -- Source is Haskell, hs-boot, external core
+        ms_location  :: ModLocation,           -- Location
+        ms_hs_date   :: ClockTime,             -- Timestamp of source file
+       ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
+        ms_srcimps   :: [Located Module],      -- Source imports
+        ms_imps      :: [Located Module],      -- Non-source imports
+        ms_hspp_file :: Maybe FilePath,                -- Filename of preprocessed source,
+                                               -- once we have preprocessed it.
+       ms_hspp_buf  :: Maybe StringBuffer      -- The actual preprocessed source, maybe.
+     }
 
-addInstsToPool :: InstPool -> [(Name, Gated IfaceInst)] -> InstPool
-addInstsToPool insts new_insts
-  = foldr add insts new_insts
-  where
-    add :: (Name, Gated IfaceInst) -> NameEnv [Gated IfaceInst] -> NameEnv [Gated IfaceInst]
-    add (cls,new_inst) insts = extendNameEnv_C combine insts cls [new_inst]
-       where
-         combine old_insts _ = new_inst : old_insts
+-- The ModLocation contains both the original source filename and the
+-- filename of the cleaned-up source file after all preprocessing has been
+-- done.  The point is that the summariser will have to cpp/unlit/whatever
+-- all files anyway, and there's no point in doing this twice -- just 
+-- park the result in a temp file, put the name of it in the location,
+-- and let @compile@ read from that file on the way back up.
+
+-- The ModLocation is stable over successive up-sweeps in GHCi, wheres
+-- the ms_hs_date and imports can, of course, change
+
+msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
+msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
+msHiFilePath  ms = ml_hi_file  (ms_location ms)
+msObjFilePath ms = ml_obj_file (ms_location ms)
+
+isBootSummary :: ModSummary -> Bool
+isBootSummary ms = isHsBoot (ms_hsc_src ms)
+
+instance Outputable ModSummary where
+   ppr ms
+      = sep [text "ModSummary {",
+             nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
+                          text "ms_mod =" <+> ppr (ms_mod ms) 
+                               <> text (hscSourceString (ms_hsc_src ms)) <> comma,
+                          text "ms_imps =" <+> ppr (ms_imps ms),
+                          text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
+             char '}'
+            ]
+
+showModMsg :: Bool -> ModSummary -> String
+showModMsg use_object mod_summary
+  = showSDoc (hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
+                   char '(', text (msHsFilePath mod_summary) <> comma,
+                   if use_object then text (msObjFilePath mod_summary)
+                             else text "interpreted",
+                   char ')'])
+ where 
+    mod     = ms_mod mod_summary 
+    mod_str = moduleString mod ++ hscSourceString (ms_hsc_src mod_summary)
 \end{code}
 
 
@@ -840,12 +1023,17 @@ data Linkable = LM {
   linkableTime     :: ClockTime,       -- Time at which this linkable was built
                                        -- (i.e. when the bytecodes were produced,
                                        --       or the mod date on the files)
-  linkableModName  :: ModuleName,      -- Should be Module, but see below
+  linkableModule   :: Module,          -- Should be Module, but see below
   linkableUnlinked :: [Unlinked]
  }
 
 isObjectLinkable :: Linkable -> Bool
-isObjectLinkable l = all isObject (linkableUnlinked l)
+isObjectLinkable l = not (null unlinked) && all isObject unlinked
+  where unlinked = linkableUnlinked l
+       -- A linkable with no Unlinked's is treated as a BCO.  We can
+       -- generate a linkable with no Unlinked's as a result of
+       -- compiling a module in HscNothing mode, and this choice
+       -- happens to work well with checkStability in module GHC.
 
 instance Outputable Linkable where
    ppr (LM when_made mod unlinkeds)