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
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:
| ... | ... | @@ -355,14 +355,14 @@ handleRunStatus step expr bindings final_ids status history0 = do |
| 355 | 355 | decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi
|
| 356 | 356 | |
| 357 | 357 | -- Was this breakpoint explicitly enabled (ie. in @BreakArray@)?
|
| 358 | - b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi)
|
|
| 358 | + bactive <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi)
|
|
| 359 | 359 | |
| 360 | 360 | apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref
|
| 361 | 361 | resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
|
| 362 | 362 | |
| 363 | 363 | -- This breakpoint is enabled or we mean to break here;
|
| 364 | 364 | -- we want to stop instead of just logging it.
|
| 365 | - if b || breakHere step span then do
|
|
| 365 | + if breakHere bactive step span then do
|
|
| 366 | 366 | -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break.
|
| 367 | 367 | -- Specifically, for :steplocal or :stepmodule, don't return control
|
| 368 | 368 | -- 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 |
| 386 | 386 | setSession hsc_env2
|
| 387 | 387 | return (ExecBreak names (Just ibi))
|
| 388 | 388 | else do
|
| 389 | + -- resume with the same step type
|
|
| 389 | 390 | let eval_opts = initEvalOpts dflags (enableGhcStepMode step)
|
| 390 | 391 | status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv
|
| 391 | 392 | history <- if not tracing then pure history0 else do
|
| ... | ... | @@ -451,7 +452,7 @@ resumeExec step mbCnt |
| 451 | 452 | hist' = case mb_brkpt of
|
| 452 | 453 | Nothing -> pure prevHistoryLst
|
| 453 | 454 | Just bi
|
| 454 | - | breakHere step span -> do
|
|
| 455 | + | breakHere False step span -> do
|
|
| 455 | 456 | hist1 <- liftIO (mkHistory hsc_env apStack bi)
|
| 456 | 457 | return $ hist1 `consBL` fromListBL 50 hist
|
| 457 | 458 | | otherwise -> pure prevHistoryLst
|
| ... | ... | @@ -49,6 +49,11 @@ data SingleStep |
| 49 | 49 | |
| 50 | 50 | -- | :stepout
|
| 51 | 51 | | StepOut
|
| 52 | + { initiatedFrom :: Maybe SrcSpan
|
|
| 53 | + -- ^ Step-out locations are filtered to make sure we don't stop at a
|
|
| 54 | + -- continuation that is within the function from which step-out was
|
|
| 55 | + -- initiated. See Note [Debugger: Step-out]
|
|
| 56 | + }
|
|
| 52 | 57 | |
| 53 | 58 | -- | :steplocal [expr]
|
| 54 | 59 | | LocalStep
|
| ... | ... | @@ -62,24 +67,73 @@ data SingleStep |
| 62 | 67 | -- step at every breakpoint or after every return (see @'EvalStep'@).
|
| 63 | 68 | enableGhcStepMode :: SingleStep -> EvalStep
|
| 64 | 69 | enableGhcStepMode RunToCompletion = EvalStepNone
|
| 65 | -enableGhcStepMode StepOut = EvalStepOut
|
|
| 70 | +enableGhcStepMode StepOut{} = EvalStepOut
|
|
| 66 | 71 | -- for the remaining step modes we need to stop at every single breakpoint.
|
| 67 | 72 | enableGhcStepMode _ = EvalStepSingle
|
| 68 | 73 | |
| 69 | --- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return
|
|
| 70 | --- @True@ if based on the step-mode alone we should stop at this breakpoint.
|
|
| 74 | +-- | Given a 'SingleStep' mode, whether the breakpoint was explicitly active,
|
|
| 75 | +-- and the SrcSpan of a breakpoint we hit, return @True@ if we should stop at
|
|
| 76 | +-- this breakpoint.
|
|
| 71 | 77 | --
|
| 72 | 78 | -- In particular, this will always be @False@ for @'RunToCompletion'@ and
|
| 73 | 79 | -- @'RunAndLogSteps'@. We'd need further information e.g. about the user
|
| 74 | 80 | -- breakpoints to determine whether to break in those modes.
|
| 75 | -breakHere :: SingleStep -> SrcSpan -> Bool
|
|
| 76 | -breakHere step break_span = case step of
|
|
| 77 | - RunToCompletion -> False
|
|
| 78 | - RunAndLogSteps -> False
|
|
| 79 | - StepOut -> True
|
|
| 80 | - SingleStep -> True
|
|
| 81 | - LocalStep span -> break_span `isSubspanOf` span
|
|
| 82 | - ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span
|
|
| 81 | +breakHere :: Bool -- ^ Was this breakpoint explicitly active (in the @BreakArray@s)?
|
|
| 82 | + -> SingleStep -- ^ What kind of stepping were we doing
|
|
| 83 | + -> SrcSpan -- ^ The span of the breakpoint we hit
|
|
| 84 | + -> Bool -- ^ Should we stop here then?
|
|
| 85 | +breakHere b RunToCompletion _ = b
|
|
| 86 | +breakHere b RunAndLogSteps _ = b
|
|
| 87 | +breakHere _ SingleStep _ = True
|
|
| 88 | +breakHere b step break_span = case step of
|
|
| 89 | + LocalStep start_span -> b || break_span `isSubspanOf` start_span
|
|
| 90 | + ModuleStep start_span -> b || srcSpanFileName_maybe start_span == srcSpanFileName_maybe break_span
|
|
| 91 | + StepOut Nothing -> True
|
|
| 92 | + StepOut (Just start) ->
|
|
| 93 | + -- See Note [Debugger: Filtering step-out stops]
|
|
| 94 | + not (break_span `isSubspanOf` start)
|
|
| 95 | + |
|
| 96 | +{-
|
|
| 97 | +Note [Debugger: Filtering step-out stops]
|
|
| 98 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 99 | +Recall from Note [Debugger: Step-out] that the RTS explicitly enables the
|
|
| 100 | +breakpoint at the start of the first continuation frame on the stack, when
|
|
| 101 | +the step-out flag is set.
|
|
| 102 | + |
|
| 103 | +Often, the continuation on top of the stack will be part of the same function
|
|
| 104 | +from which step-out was initiated. A trivial example is a case expression:
|
|
| 105 | + |
|
| 106 | + f x = case <brk>g x of ...
|
|
| 107 | + |
|
| 108 | +If we're stopped in <brk>, the continuation will be case alternatives rather
|
|
| 109 | +than in the function which called `f`. This is especially relevant for monadic
|
|
| 110 | +do-blocks which may end up being compiled to long chains of case expressions,
|
|
| 111 | +such as IO, and we don't want to stop at every line in the block while stepping out!
|
|
| 112 | + |
|
| 113 | +To make sure we only stop at a continuation outside of the current function, we
|
|
| 114 | +compare the continuation breakpoint `SrcSpan` against the current one. If the
|
|
| 115 | +continuation breakpoint is within the current function, instead of stopping, we
|
|
| 116 | +re-trigger step-out and return the RTS interpreter right away.
|
|
| 117 | + |
|
| 118 | +This behaviour is very similar to `:steplocal`, which is implemented by
|
|
| 119 | +yielding from the RTS at every breakpoint (using `:step`) but only really
|
|
| 120 | +stopping when the breakpoint's `SrcSpan` is contained in the current function.
|
|
| 121 | + |
|
| 122 | +The function which determines if we should stop at the current breakpoint is
|
|
| 123 | +`breakHere`. For `StepOut`, `breakHere` will only return `True` if the
|
|
| 124 | +breakpoint is not contained in the function from which step-out was initiated.
|
|
| 125 | + |
|
| 126 | +Notably, this means we will ignore breakpoints enabled by the user if they are
|
|
| 127 | +contained in the function we are stepping out of.
|
|
| 128 | + |
|
| 129 | +If we had a way to distinguish whether a breakpoint was explicitly enabled (in
|
|
| 130 | +`BreakArrays`) by the user vs by step-out we could additionally break on
|
|
| 131 | +user-enabled breakpoints; however, it's not a straightforward and arguably it
|
|
| 132 | +may be uncommon for a user to use step-out to run until the next breakpoint in
|
|
| 133 | +the same function. Of course, if a breakpoint in any other function is hit
|
|
| 134 | +before returning to the continuation, we will still stop there (`breakHere`
|
|
| 135 | +will be `True` because the break point is not within the initiator function).
|
|
| 136 | +-}
|
|
| 83 | 137 | |
| 84 | 138 | data ExecResult
|
| 85 | 139 |
| ... | ... | @@ -4165,7 +4165,14 @@ stepCmd arg = withSandboxOnly ":step" $ step arg |
| 4165 | 4165 | step expression = runStmt expression GHC.SingleStep >> return ()
|
| 4166 | 4166 | |
| 4167 | 4167 | stepOutCmd :: GhciMonad m => String -> m ()
|
| 4168 | -stepOutCmd _ = withSandboxOnly ":stepout" $ doContinue GHC.StepOut
|
|
| 4168 | +stepOutCmd _ = withSandboxOnly ":stepout" $ do
|
|
| 4169 | + mb_span <- getCurrentBreakSpan
|
|
| 4170 | + case mb_span of
|
|
| 4171 | + Nothing -> doContinue (GHC.StepOut Nothing)
|
|
| 4172 | + Just loc -> do
|
|
| 4173 | + md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule
|
|
| 4174 | + current_toplevel_decl <- flip enclosingTickSpan loc <$> getTickArray md
|
|
| 4175 | + doContinue (GHC.StepOut (Just (RealSrcSpan current_toplevel_decl Strict.Nothing)))
|
|
| 4169 | 4176 | |
| 4170 | 4177 | stepLocalCmd :: GhciMonad m => String -> m ()
|
| 4171 | 4178 | stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg
|
| ... | ... | @@ -361,6 +361,11 @@ By simply enabling the breakpoint heading the continuation we can ensure that |
| 361 | 361 | when it is returned to we will stop there without additional work -- it
|
| 362 | 362 | leverages the existing break point insertion process and stopping mechanisms.
|
| 363 | 363 | |
| 364 | +See Note [Debugger: Filtering step-out stops] for details on how the
|
|
| 365 | +interpreter further filters the continuation we stop at to make sure we onky
|
|
| 366 | +break on a continuation outside of the function from which step-out was
|
|
| 367 | +initiated.
|
|
| 368 | + |
|
| 364 | 369 | A limitation of this approach is that stepping-out of a function that was
|
| 365 | 370 | tail-called will skip its caller since no stack frame is pushed for a tail
|
| 366 | 371 | call (i.e. a tail call returns directly to its caller's first non-tail caller).
|
| ... | ... | @@ -10,8 +10,5 @@ _result :: |
| 10 | 10 | ^^^^^^^^^^^^^^^^^
|
| 11 | 11 | 7 putStrLn "hello3"
|
| 12 | 12 | hello2
|
| 13 | -Stopped in Main.main, T26042d.hs:7:3-19
|
|
| 14 | -_result ::
|
|
| 15 | - GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
|
|
| 16 | - -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
|
|
| 17 | - () #) = _ |
|
| 13 | +hello3
|
|
| 14 | +hello4 |