[Git][ghc/ghc][wip/ghci-force-background] ghci: Force bytecode to be evaluated after loading
Matthew Pickering (@mpickering)
gitlab at gitlab.haskell.org
Wed Jan 29 17:46:44 UTC 2025
Matthew Pickering pushed to branch wip/ghci-force-background at Glasgow Haskell Compiler / GHC
Commits:
2a66eb15 by Matthew Pickering at 2025-01-29T17:46:32+00:00
ghci: Force bytecode to be evaluated after loading
Behaviour before: Bytecode is forced when you need it to evaluate an
expression in the interpreter.
Behaviour after: Bytecode is forced in parallel, in the background, after
the initial load is completed.
The goal is to increase percieved responsiveness of the interpreter
after a reload. If you do a reload and at a later point perform
evaluation, now the evaluation will start immediately, rather than
waiting first for all the byte code to be compiled.
Since the bytecode is evaluated in the background, the prompt can still
be used like normal to evaluate expressions or perform other queries.
The thunks are evaluated in parallel by creating a spark for each thunk,
thus if another reload is perfomed then the sparks will be discarded as
the thunks in question will no longer be evaluated.
- - - - -
2 changed files:
- compiler/GHC/Unit/Home/PackageTable.hs
- ghc/GHCi/UI.hs
Changes:
=====================================
compiler/GHC/Unit/Home/PackageTable.hs
=====================================
@@ -47,6 +47,7 @@ module GHC.Unit.Home.PackageTable
-- ** More Traversal-based queries
, hptCollectDependencies
, hptCollectObjects
+ , hptCollectByteCode
, hptCollectModules
-- ** Memory dangerous queries
@@ -248,6 +249,12 @@ hptCollectObjects HPT{table} = do
return $
foldr ((:) . expectJust "collectObjects" . homeModInfoObject) [] hpt
+hptCollectByteCode :: HomePackageTable -> IO [Linkable]
+hptCollectByteCode HPT{table} = do
+ hpt <- readIORef table
+ return $
+ catMaybes $ foldr ((:) . homeModInfoByteCode) [] hpt
+
-- | Collect all module ifaces in the HPT
--
-- $O(n)$ in the number of modules in the HPT.
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -94,6 +94,8 @@ import GHC.Unit.Finder as Finder
import GHC.Unit.Module.Graph (filterToposortToModules)
import GHC.Unit.Module.ModSummary
+import GHC.Linker.Types
+
import GHC.Data.StringBuffer
import GHC.Utils.Outputable
import GHC.Utils.Logger
@@ -176,6 +178,8 @@ import GHC.TopHandler ( topHandler )
import qualified GHC.Unit.Module.Graph as GHC
+import GHC.Conc.Sync ( par, pseq, forkIO )
+
-----------------------------------------------------------------------------
data GhciSettings = GhciSettings {
@@ -2170,6 +2174,34 @@ afterLoad ok load_type = do
modulesLoadedMsg ok loaded_mods load_type
graph <- GHC.getModuleGraph
setContextAfterLoad (isReload load_type) (Just graph)
+ forceByteCode
+
+-- | Force any compiled bytecode in the background
+--
+-- During compilation the compiler leaves thunks when producing bytecode, so that
+-- the result is not forced before it is needed. (Especially important when doing recompilation
+-- checking)
+--
+-- However, after the reload is complete, the interpreter will otherwise be idle, so
+-- force those thunks in parallel so that when the user comes to write in the prompt
+-- the response is faster.
+forceByteCode :: GhciMonad m => m ()
+forceByteCode = do
+ hsc_env <- GHC.getSession
+ -- Spawn a new thread, so the thunks are forced completely in the background of the main thread
+ -- and we can get to the prompt as fast as possible.
+ void $ liftIO $ forkIO $ do
+ all_linkables <- liftIO (concat <$> traverse (hptCollectByteCode . homeUnitEnv_hpt) (hsc_HUG hsc_env))
+ liftIO $ evaluate $ foldr (\x u -> force x `pseq` u) () all_linkables
+
+ where
+
+ force :: Linkable -> ()
+ force (Linkable _ _ ps) = foldr (\a u -> force_part a `par` u) () ps
+
+ force_part (LazyBCOs x _) = x `par` ()
+ force_part _ = ()
+
setContextAfterLoad :: GhciMonad m => Bool -> Maybe GHC.ModuleGraph -> m ()
setContextAfterLoad keep_ctxt Nothing = do
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2a66eb15f744d876acedf7a42db7cdd2196bd6e9
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2a66eb15f744d876acedf7a42db7cdd2196bd6e9
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250129/6ce7b947/attachment-0001.html>
More information about the ghc-commits
mailing list