fix for compiling the base package with --make
[ghc-hetmet.git] / ghc / compiler / main / HscTypes.lhs
index b02debb..00e1b49 100644 (file)
@@ -12,7 +12,7 @@ module HscTypes (
        ModuleGraph, emptyMG,
 
        ModDetails(..), emptyModDetails,
-       ModGuts(..), ModImports(..), ForeignStubs(..),
+       ModGuts(..), CgGuts(..), ModImports(..), ForeignStubs(..),
 
        ModSummary(..), showModMsg, isBootSummary,
        msHsFilePath, msHiFilePath, msObjFilePath, 
@@ -84,9 +84,10 @@ import Type          ( TyThing(..) )
 import Class           ( Class, classSelIds, classTyCon )
 import TyCon           ( TyCon, tyConSelIds, tyConDataCons )
 import DataCon         ( dataConImplicitIds )
-import Packages                ( PackageIdH, PackageId, PackageConfig )
+import PrelNames       ( gHC_PRIM )
+import Packages                ( PackageIdH, PackageId, PackageConfig, HomeModules )
 import DynFlags                ( DynFlags(..), isOneShot )
-import DriverPhases    ( HscSource(..), isHsBoot, hscSourceString )
+import DriverPhases    ( HscSource(..), isHsBoot, hscSourceString, Phase )
 import BasicTypes      ( Version, initialVersion, IPName, 
                          Fixity, defaultFixity, DeprecTxt )
 
@@ -94,9 +95,9 @@ import IfaceSyn               ( IfaceInst, IfaceRule, IfaceDecl(ifName) )
 
 import FiniteMap       ( FiniteMap )
 import CoreSyn         ( CoreRule )
-import Maybes          ( orElse, fromJust, expectJust )
+import Maybes          ( orElse, expectJust, expectJust )
 import Outputable
-import SrcLoc          ( SrcSpan )
+import SrcLoc          ( SrcSpan, Located )
 import UniqSupply      ( UniqSupply )
 import FastString      ( FastString )
 
@@ -188,15 +189,20 @@ hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
 data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
 
 data TargetId
-  = TargetModule Module           -- ^ A module name: search for the file
-  | TargetFile   FilePath  -- ^ A filename: parse it to find the module name.
+  = 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
+pprTargetId (TargetFile f _) = text f
 
 type FinderCache = ModuleEnv FinderCacheEntry
 type FinderCacheEntry = (ModLocation, Maybe (PackageConfig,Bool))
@@ -220,6 +226,10 @@ data HomeModInfo
                --      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.
@@ -266,9 +276,17 @@ hptRules hsc_env deps
     |  -- 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 = ASSERT( mod `elemModuleEnv` hpt )
-                    fromJust (lookupModuleEnv hpt mod)
+    , 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) ]
@@ -332,9 +350,19 @@ data ModIface
        mi_decls :: [(Version,IfaceDecl)],      -- Sorted
 
         mi_globals  :: !(Maybe GlobalRdrEnv),
-               -- Its top level environment or Nothing if we read this
-               -- interface from an interface file.  (We need the source
-               -- file to figure out the top-level environment.)
+               -- 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
@@ -378,6 +406,7 @@ data ModGuts
        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
@@ -398,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
@@ -427,6 +472,7 @@ data ModImports
                                                --      directly or indirectly
     }
 
+-----------------------------------
 data ForeignStubs = NoStubs
                  | ForeignStubs
                        SDoc            -- Header file prototypes for
@@ -640,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
@@ -780,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}
 
 
@@ -902,8 +960,8 @@ data ModSummary
         ms_location  :: ModLocation,           -- Location
         ms_hs_date   :: ClockTime,             -- Timestamp of source file
        ms_obj_date  :: Maybe ClockTime,        -- Timestamp of object, maybe
-        ms_srcimps   :: [Module],              -- Source imports
-        ms_imps      :: [Module],              -- Non-source imports
+        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.
@@ -947,7 +1005,7 @@ showModMsg use_object mod_summary
                    char ')'])
  where 
     mod     = ms_mod mod_summary 
-    mod_str = moduleUserString mod ++ hscSourceString (ms_hsc_src mod_summary)
+    mod_str = moduleString mod ++ hscSourceString (ms_hsc_src mod_summary)
 \end{code}
 
 
@@ -970,7 +1028,12 @@ data Linkable = LM {
  }
 
 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)