[Git][ghc/ghc][wip/romes/step-out-5] debugger: Filter step-out stops by SrcSpan

Rodrigo Mesquita pushed to branch wip/romes/step-out-5 at Glasgow Haskell Compiler / GHC Commits: 5df3c3fc by Rodrigo Mesquita at 2025-06-19T12:59:26+01:00 debugger: Filter step-out stops by SrcSpan To implement step-out, the RTS looks for the first continuation frame on the stack and explicitly enables its entry breakpoint. However, some continuations will be contained in the function from which step-out was initiated (trivial example is a case expression). Similarly to steplocal, we will filter the breakpoints at which the RTS yields to the debugger based on the SrcSpan. When doing step-out, only stop if the breakpoint is /not/ contained in the function from which we initiated it. This is especially relevant in monadic statements such as IO which is compiled to a long chain of case expressions. See Note [Debugger: Filtering step-out stops] - - - - - 5 changed files: - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - ghc/GHCi/UI.hs - rts/Interpreter.c - testsuite/tests/ghci.debugger/scripts/T26042d.stdout Changes: ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -355,14 +355,14 @@ handleRunStatus step expr bindings final_ids status history0 = do decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi -- Was this breakpoint explicitly enabled (ie. in @BreakArray@)? - b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) + bactive <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi) apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt -- This breakpoint is enabled or we mean to break here; -- we want to stop instead of just logging it. - if b || breakHere step span then do + if breakHere bactive step span then do -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break. -- Specifically, for :steplocal or :stepmodule, don't return control -- and simply resume execution from here until we hit a breakpoint we do want to stop at. @@ -386,6 +386,7 @@ handleRunStatus step expr bindings final_ids status history0 = do setSession hsc_env2 return (ExecBreak names (Just ibi)) else do + -- resume with the same step type let eval_opts = initEvalOpts dflags (enableGhcStepMode step) status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv history <- if not tracing then pure history0 else do @@ -451,7 +452,7 @@ resumeExec step mbCnt hist' = case mb_brkpt of Nothing -> pure prevHistoryLst Just bi - | breakHere step span -> do + | breakHere False step span -> do hist1 <- liftIO (mkHistory hsc_env apStack bi) return $ hist1 `consBL` fromListBL 50 hist | otherwise -> pure prevHistoryLst ===================================== compiler/GHC/Runtime/Eval/Types.hs ===================================== @@ -49,6 +49,11 @@ data SingleStep -- | :stepout | StepOut + { initiatedFrom :: Maybe SrcSpan + -- ^ Step-out locations are filtered to make sure we don't stop at a + -- continuation that is within the function from which step-out was + -- initiated. See Note [Debugger: Step-out] + } -- | :steplocal [expr] | LocalStep @@ -62,24 +67,73 @@ data SingleStep -- step at every breakpoint or after every return (see @'EvalStep'@). enableGhcStepMode :: SingleStep -> EvalStep enableGhcStepMode RunToCompletion = EvalStepNone -enableGhcStepMode StepOut = EvalStepOut +enableGhcStepMode StepOut{} = EvalStepOut -- for the remaining step modes we need to stop at every single breakpoint. enableGhcStepMode _ = EvalStepSingle --- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return --- @True@ if based on the step-mode alone we should stop at this breakpoint. +-- | Given a 'SingleStep' mode, whether the breakpoint was explicitly active, +-- and the SrcSpan of a breakpoint we hit, return @True@ if we should stop at +-- this breakpoint. -- -- In particular, this will always be @False@ for @'RunToCompletion'@ and -- @'RunAndLogSteps'@. We'd need further information e.g. about the user -- breakpoints to determine whether to break in those modes. -breakHere :: SingleStep -> SrcSpan -> Bool -breakHere step break_span = case step of - RunToCompletion -> False - RunAndLogSteps -> False - StepOut -> True - SingleStep -> True - LocalStep span -> break_span `isSubspanOf` span - ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span +breakHere :: Bool -- ^ Was this breakpoint explicitly active (in the @BreakArray@s)? + -> SingleStep -- ^ What kind of stepping were we doing + -> SrcSpan -- ^ The span of the breakpoint we hit + -> Bool -- ^ Should we stop here then? +breakHere b RunToCompletion _ = b +breakHere b RunAndLogSteps _ = b +breakHere _ SingleStep _ = True +breakHere b step break_span = case step of + LocalStep start_span -> b || break_span `isSubspanOf` start_span + ModuleStep start_span -> b || srcSpanFileName_maybe start_span == srcSpanFileName_maybe break_span + StepOut Nothing -> True + StepOut (Just start) -> + -- See Note [Debugger: Filtering step-out stops] + not (break_span `isSubspanOf` start) + +{- +Note [Debugger: Filtering step-out stops] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Recall from Note [Debugger: Step-out] that the RTS explicitly enables the +breakpoint at the start of the first continuation frame on the stack, when +the step-out flag is set. + +Often, the continuation on top of the stack will be part of the same function +from which step-out was initiated. A trivial example is a case expression: + + f x = case <brk>g x of ... + +If we're stopped in <brk>, the continuation will be case alternatives rather +than in the function which called `f`. This is especially relevant for monadic +do-blocks which may end up being compiled to long chains of case expressions, +such as IO, and we don't want to stop at every line in the block while stepping out! + +To make sure we only stop at a continuation outside of the current function, we +compare the continuation breakpoint `SrcSpan` against the current one. If the +continuation breakpoint is within the current function, instead of stopping, we +re-trigger step-out and return the RTS interpreter right away. + +This behaviour is very similar to `:steplocal`, which is implemented by +yielding from the RTS at every breakpoint (using `:step`) but only really +stopping when the breakpoint's `SrcSpan` is contained in the current function. + +The function which determines if we should stop at the current breakpoint is +`breakHere`. For `StepOut`, `breakHere` will only return `True` if the +breakpoint is not contained in the function from which step-out was initiated. + +Notably, this means we will ignore breakpoints enabled by the user if they are +contained in the function we are stepping out of. + +If we had a way to distinguish whether a breakpoint was explicitly enabled (in +`BreakArrays`) by the user vs by step-out we could additionally break on +user-enabled breakpoints; however, it's not a straightforward and arguably it +may be uncommon for a user to use step-out to run until the next breakpoint in +the same function. Of course, if a breakpoint in any other function is hit +before returning to the continuation, we will still stop there (`breakHere` +will be `True` because the break point is not within the initiator function). +-} data ExecResult ===================================== ghc/GHCi/UI.hs ===================================== @@ -4165,7 +4165,14 @@ stepCmd arg = withSandboxOnly ":step" $ step arg step expression = runStmt expression GHC.SingleStep >> return () stepOutCmd :: GhciMonad m => String -> m () -stepOutCmd _ = withSandboxOnly ":stepout" $ doContinue GHC.StepOut +stepOutCmd _ = withSandboxOnly ":stepout" $ do + mb_span <- getCurrentBreakSpan + case mb_span of + Nothing -> doContinue (GHC.StepOut Nothing) + Just loc -> do + md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule + current_toplevel_decl <- flip enclosingTickSpan loc <$> getTickArray md + doContinue (GHC.StepOut (Just (RealSrcSpan current_toplevel_decl Strict.Nothing))) stepLocalCmd :: GhciMonad m => String -> m () stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg ===================================== rts/Interpreter.c ===================================== @@ -361,6 +361,11 @@ By simply enabling the breakpoint heading the continuation we can ensure that when it is returned to we will stop there without additional work -- it leverages the existing break point insertion process and stopping mechanisms. +See Note [Debugger: Filtering step-out stops] for details on how the +interpreter further filters the continuation we stop at to make sure we onky +break on a continuation outside of the function from which step-out was +initiated. + A limitation of this approach is that stepping-out of a function that was tail-called will skip its caller since no stack frame is pushed for a tail call (i.e. a tail call returns directly to its caller's first non-tail caller). ===================================== testsuite/tests/ghci.debugger/scripts/T26042d.stdout ===================================== @@ -10,8 +10,5 @@ _result :: ^^^^^^^^^^^^^^^^^ 7 putStrLn "hello3" hello2 -Stopped in Main.main, T26042d.hs:7:3-19 -_result :: - GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld - -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld, - () #) = _ +hello3 +hello4 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5df3c3fcec5b08ce8bd90ebed02be5d6... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5df3c3fcec5b08ce8bd90ebed02be5d6... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Rodrigo Mesquita (@alt-romes)