summaryrefslogtreecommitdiff
path: root/compiler/GHC.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC.hs')
-rw-r--r--compiler/GHC.hs47
1 files changed, 5 insertions, 42 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index f71caa6f15..7e882dbd8b 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -57,7 +57,7 @@ module GHC (
SuccessFlag(..), succeeded, failed,
defaultWarnErrLogger, WarnErrLogger,
workingDirectoryChanged,
- parseModule, typecheckModule, desugarModule, loadModule,
+ parseModule, typecheckModule, desugarModule,
ParsedModule(..), TypecheckedModule(..), DesugaredModule(..),
TypecheckedSource, ParsedSource, RenamedSource, -- ditto
TypecheckedMod, ParsedMod,
@@ -314,7 +314,6 @@ import GHC.Driver.Config
import GHC.Driver.Main
import GHC.Driver.Make
import GHC.Driver.Hooks
-import GHC.Driver.Pipeline ( compileOne' )
import GHC.Driver.Monad
import GHC.Driver.Ppr
@@ -357,6 +356,7 @@ import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
+import GHC.Utils.Fingerprint
import GHC.Core.Predicate
import GHC.Core.Type hiding( typeKind )
@@ -387,7 +387,6 @@ import GHC.Types.TyThing
import GHC.Types.Name.Env
import GHC.Types.Name.Ppr
import GHC.Types.TypeEnv
-import GHC.Types.SourceFile
import GHC.Unit
import GHC.Unit.Env
@@ -407,7 +406,6 @@ import Data.Set (Set)
import qualified Data.Set as S
import qualified Data.Sequence as Seq
import Data.Maybe
-import Data.Time
import Data.Typeable ( Typeable )
import Data.Word ( Word8 )
import Control.Monad
@@ -750,7 +748,7 @@ setProgramDynFlags_ invalidate_needed dflags = do
-- old log_action. This is definitely wrong (#7478).
--
-- Hence, we invalidate the ModSummary cache after changing the
--- DynFlags. We do this by tweaking the date on each ModSummary, so
+-- DynFlags. We do this by tweaking the hash on each ModSummary, so
-- that the next downsweep will think that all the files have changed
-- and preprocess them again. This won't necessarily cause everything
-- to be recompiled, because by the time we check whether we need to
@@ -761,7 +759,7 @@ invalidateModSummaryCache :: GhcMonad m => m ()
invalidateModSummaryCache =
modifySession $ \h -> h { hsc_mod_graph = mapMG inval (hsc_mod_graph h) }
where
- inval ms = ms { ms_hs_date = addUTCTime (-1) (ms_hs_date ms) }
+ inval ms = ms { ms_hs_hash = fingerprint0 }
-- | Returns the program 'DynFlags'.
getProgramDynFlags :: GhcMonad m => m DynFlags
@@ -783,7 +781,7 @@ setInteractiveDynFlags dflags = do
-- Initialise (load) plugins in the interactive environment with the new
-- DynFlags
- plugin_env <- liftIO $ initializePlugins $ mkInteractiveHscEnv $
+ plugin_env <- liftIO $ flip initializePlugins Nothing $ mkInteractiveHscEnv $
hsc_env0 { hsc_IC = ic0 { ic_dflags = dflags'' }}
-- Update both plugins cache and DynFlags in the interactive context.
@@ -1185,41 +1183,6 @@ desugarModule tcm = do
dm_core_module = guts
}
--- | Load a module. Input doesn't need to be desugared.
---
--- A module must be loaded before dependent modules can be typechecked. This
--- always includes generating a 'ModIface' and, depending on the
--- @DynFlags@\'s 'GHC.Driver.Session.backend', may also include code generation.
---
--- This function will always cause recompilation and will always overwrite
--- previous compilation results (potentially files on disk).
---
-loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
-loadModule tcm = do
- let ms = modSummary tcm
- let mod = ms_mod_name ms
- let loc = ms_location ms
- let (tcg, _details) = tm_internals tcm
-
- mb_linkable <- case ms_obj_date ms of
- Just t | t > ms_hs_date ms -> do
- l <- liftIO $ findObjectLinkable (ms_mod ms)
- (ml_obj_file loc) t
- return (Just l)
- _otherwise -> return Nothing
-
- let source_modified | isNothing mb_linkable = SourceModified
- | otherwise = SourceUnmodified
- -- we can't determine stability here
-
- -- compile doesn't change the session
- hsc_env <- getSession
- mod_info <- liftIO $ compileOne' (Just tcg) Nothing
- hsc_env ms 1 1 Nothing mb_linkable
- source_modified
-
- modifySession $ hscUpdateHPT (\hpt -> addToHpt hpt mod mod_info)
- return tcm
-- %************************************************************************