[Git][ghc/ghc][wip/romes/ghci-debugger-2] ghci: Don't set virtualCWD on every iteration
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Mon Feb 24 17:12:19 UTC 2025
Rodrigo Mesquita pushed to branch wip/romes/ghci-debugger-2 at Glasgow Haskell Compiler / GHC
Commits:
0868da09 by Rodrigo Mesquita at 2025-02-24T17:12:08+00:00
ghci: Don't set virtualCWD on every iteration
When using :steplocal, we will break and resume from every breakpoint
until we find a breakpoint in the same function as the one we called
:steplocal from originally.
However, resume and exec are incredibly slow because of all the calls to
withVirtualCWD (amongst other bad inefficiencies in this loop that are
fixed by the previous and next commit)
The calls to withVirtualCWD were introduced to fix #2973, but this bug
is no longer reproducible -- regardless of the calls to withVirtualCWD.
Fixes #25779 (problem 2 of 3)
- - - - -
1 changed file:
- compiler/GHC/Runtime/Eval.hs
Changes:
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -130,14 +130,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) )
import GHC.IfaceToCore
import Control.Monad
-import Control.Monad.Catch as MC
import Data.Array
import Data.Dynamic
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List (find,intercalate)
import Data.List.NonEmpty (NonEmpty)
-import System.Directory
import Unsafe.Coerce ( unsafeCoerce )
import qualified GHC.Unit.Home.Graph as HUG
@@ -232,10 +230,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do
updateFixityEnv fix_env
status <-
- withVirtualCWD $
- liftIO $ do
- let eval_opts = initEvalOpts idflags' (isStep execSingleStep)
- evalStmt interp eval_opts (execWrap hval)
+ liftIO $ do
+ let eval_opts = initEvalOpts idflags' (isStep execSingleStep)
+ evalStmt interp eval_opts (execWrap hval)
let ic = hsc_IC hsc_env
bindings = (ic_tythings ic, ic_gre_cache ic)
@@ -282,32 +279,6 @@ them. The relevant predicate is OccName.isDerivedOccName.
See #11051 for more background and examples.
-}
-withVirtualCWD :: GhcMonad m => m a -> m a
-withVirtualCWD m = do
- hsc_env <- getSession
-
- -- a virtual CWD is only necessary when we're running interpreted code in
- -- the same process as the compiler.
- case interpInstance <$> hsc_interp hsc_env of
- Just (ExternalInterp {}) -> m
- _ -> do
- let ic = hsc_IC hsc_env
- let set_cwd = do
- dir <- liftIO $ getCurrentDirectory
- case ic_cwd ic of
- Just dir -> liftIO $ setCurrentDirectory dir
- Nothing -> return ()
- return dir
-
- reset_cwd orig_dir = do
- virt_dir <- liftIO $ getCurrentDirectory
- hsc_env <- getSession
- let old_IC = hsc_IC hsc_env
- setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } }
- liftIO $ setCurrentDirectory orig_dir
-
- MC.bracket set_cwd reset_cwd $ \_ -> m
-
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr
@@ -453,7 +424,7 @@ resumeExec step_here step mbCnt
, resumeBreakpointId = mb_brkpt
, resumeSpan = span
, resumeHistory = hist } ->
- withVirtualCWD $ do
+ do
-- When the user specified a break ignore count, set it
-- in the interpreter
case (mb_brkpt, mbCnt) of
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0868da0976b30be7e3e351297bb745572bf21be0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0868da0976b30be7e3e351297bb745572bf21be0
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/20250224/eaf320f2/attachment-0001.html>
More information about the ghc-commits
mailing list