
Rodrigo Mesquita pushed to branch wip/romes/per-thread-step-in at Glasgow Haskell Compiler / GHC Commits: ac7b34fd by Rodrigo Mesquita at 2025-05-23T15:54:43+01:00 debugger/rts: Allow toggling step-in per thread The RTS global flag `rts_stop_next_breakpoint` globally sets the interpreter to stop at the immediate next breakpoint. With this commit, single step mode can additionally be set per thread in the TSO flag (TSO_STOP_NEXT_BREAKPOINT). Being able to toggle "stop at next breakpoint" per thread is an important requirement for implementing "stepping out" of a function in a multi-threaded context. And, more generally, having a per-thread flag for single-stepping paves the way for multi-threaded debugging. That said, when we want to enable "single step" mode for the whole interpreted program we still want to stop at the immediate next breakpoint, whichever thread it belongs to. That's why we also keep the global `rts_stop_next_breakpoint` flag, with `rts_enableStopNextBreakpointAll` and `rts_disableStopNextBreakpointAll` helpers. Preparation for #26042 - - - - - 11 changed files: - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghci/GHCi/Debugger.hs - libraries/ghci/GHCi/Run.hs - libraries/ghci/ghci.cabal.in - rts/Interpreter.c - rts/Interpreter.h - rts/RtsSymbols.c - rts/include/rts/Constants.h Changes: ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -624,6 +624,7 @@ data TsoFlags | TsoMarked | TsoSqueezed | TsoAllocLimit + | TsoStopNextBreakpoint | TsoFlagsUnknownValue Word32 -- ^ Please report this as a bug deriving (Eq, Show, Generic, Ord) ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc ===================================== @@ -87,6 +87,9 @@ parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +#if __GLASGOW_HASKELL__ >= 913 + | isSet (#const TSO_STOP_NEXT_BREAKPOINT) w = TsoStopNextBreakpoint : parseTsoFlags (unset (#const TSO_STOP_NEXT_BREAKPOINT) w) +#endif parseTsoFlags 0 = [] parseTsoFlags w = [TsoFlagsUnknownValue w] ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc ===================================== @@ -87,6 +87,9 @@ parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +#if __GLASGOW_HASKELL__ >= 913 + | isSet (#const TSO_STOP_NEXT_BREAKPOINT) w = TsoStopNextBreakpoint : parseTsoFlags (unset (#const TSO_STOP_NEXT_BREAKPOINT) w) +#endif parseTsoFlags 0 = [] parseTsoFlags w = [TsoFlagsUnknownValue w] ===================================== libraries/ghc-heap/tests/parse_tso_flags.hs ===================================== @@ -13,5 +13,6 @@ main = do assertEqual (parseTsoFlags 64) [TsoMarked] assertEqual (parseTsoFlags 128) [TsoSqueezed] assertEqual (parseTsoFlags 256) [TsoAllocLimit] + assertEqual (parseTsoFlags 512) [TsoStopNextBreakpoint] assertEqual (parseTsoFlags 6) [TsoLocked, TsoBlockx] ===================================== libraries/ghci/GHCi/Debugger.hs ===================================== @@ -0,0 +1,67 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} +module GHCi.Debugger + ( + -- * Single step mode + rts_enableStopNextBreakpoint + , rts_enableStopNextBreakpointAll + , rts_disableStopNextBreakpoint + , rts_disableStopNextBreakpointAll + + -- * Stop on exception + , exceptionFlag + + -- * Breakpoint Callback + , BreakpointCallback + , breakPointIOAction + ) where + +import Prelude -- See note [Why do we import Prelude here?] + +import GHC.Base (ThreadId#, Addr#, Int#) +import Foreign.C (CInt) +import Foreign (StablePtr, Ptr) +import GHCi.RemoteTypes (HValue) + +-------------------------------------------------------------------------------- +-- Single step mode + +-- | Enables the single step mode for a specific thread, thus stopping only on +-- breakpoints in that thread. +foreign import ccall unsafe "rts_enableStopNextBreakpoint" + rts_enableStopNextBreakpoint :: ThreadId# -> IO () + +-- | Disables per-thread single-step mode. Note: if global single-step is +-- enabled we stop at all breakpoints regardless of the per-thread flag. +foreign import ccall unsafe "rts_disableStopNextBreakpoint" + rts_disableStopNextBreakpoint :: ThreadId# -> IO () + +-- | Enables the single step mode for all threads, thus stopping at any +-- existing breakpoint. +foreign import ccall unsafe "rts_enableStopNextBreakpointAll" + rts_enableStopNextBreakpointAll :: IO () + +-- | Disables the single step mode for all threads +foreign import ccall unsafe "rts_disableStopNextBreakpointAll" + rts_disableStopNextBreakpointAll :: IO () + +-------------------------------------------------------------------------------- + +foreign import ccall "&rts_stop_on_exception" exceptionFlag :: Ptr CInt + +-------------------------------------------------------------------------------- + +type BreakpointCallback + = Addr# -- pointer to the breakpoint tick module name + -> Addr# -- pointer to the breakpoint tick module unit id + -> Int# -- breakpoint tick index + -> Addr# -- pointer to the breakpoint info module name + -> Addr# -- pointer to the breakpoint info module unit id + -> Int# -- breakpoint info index + -> Bool -- exception? + -> HValue -- the AP_STACK, or exception + -> IO () + +foreign import ccall "&rts_breakpoint_io_action" + breakPointIOAction :: Ptr (StablePtr BreakpointCallback) + ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -1,5 +1,5 @@ {-# LANGUAGE GADTs, RecordWildCards, MagicHash, ScopedTypeVariables, CPP, - UnboxedTuples, LambdaCase #-} + UnboxedTuples, LambdaCase, UnliftedFFITypes #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -- | @@ -20,6 +20,7 @@ import GHCi.InfoTable #endif import qualified GHC.InfoProv as InfoProv +import GHCi.Debugger import GHCi.FFI import GHCi.Message import GHCi.ObjLink @@ -332,7 +333,7 @@ withBreakAction opts breakMVar statusMVar act stablePtr <- newStablePtr onBreak poke breakPointIOAction stablePtr when (breakOnException opts) $ poke exceptionFlag 1 - when (singleStep opts) $ setStepFlag + when (singleStep opts) rts_enableStopNextBreakpointAll return stablePtr -- Breaking on exceptions is not enabled by default, since it -- might be a bit surprising. The exception flag is turned off @@ -363,7 +364,7 @@ withBreakAction opts breakMVar statusMVar act resetBreakAction stablePtr = do poke breakPointIOAction noBreakStablePtr poke exceptionFlag 0 - resetStepFlag + rts_disableStopNextBreakpointAll freeStablePtr stablePtr resumeStmt @@ -396,28 +397,6 @@ abandonStmt hvref = do _ <- takeMVar resumeStatusMVar return () -foreign import ccall "&rts_stop_next_breakpoint" stepFlag :: Ptr CInt -foreign import ccall "&rts_stop_on_exception" exceptionFlag :: Ptr CInt - -setStepFlag :: IO () -setStepFlag = poke stepFlag 1 -resetStepFlag :: IO () -resetStepFlag = poke stepFlag 0 - -type BreakpointCallback - = Addr# -- pointer to the breakpoint tick module name - -> Addr# -- pointer to the breakpoint tick module unit id - -> Int# -- breakpoint tick index - -> Addr# -- pointer to the breakpoint info module name - -> Addr# -- pointer to the breakpoint info module unit id - -> Int# -- breakpoint info index - -> Bool -- exception? - -> HValue -- the AP_STACK, or exception - -> IO () - -foreign import ccall "&rts_breakpoint_io_action" - breakPointIOAction :: Ptr (StablePtr BreakpointCallback) - noBreakStablePtr :: StablePtr BreakpointCallback noBreakStablePtr = unsafePerformIO $ newStablePtr noBreakAction ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -60,6 +60,7 @@ library CPP-Options: -DHAVE_INTERNAL_INTERPRETER exposed-modules: GHCi.Run + GHCi.Debugger GHCi.CreateBCO GHCi.ObjLink GHCi.Signals ===================================== rts/Interpreter.c ===================================== @@ -243,9 +243,44 @@ allocate_NONUPD (Capability *cap, int n_words) return allocate(cap, stg_max(sizeofW(StgHeader)+MIN_PAYLOAD_SIZE, n_words)); } -int rts_stop_next_breakpoint = 0; int rts_stop_on_exception = 0; +/* --------------------------------------------------------------------------- + * Enabling and disabling global single step mode + * ------------------------------------------------------------------------ */ + +/* A global toggle for single-step mode. + * Unlike `TSO_STOP_NEXT_BREAKPOINT`, which sets single-step mode per-thread, + * `rts_stop_next_breakpoint` globally enables single-step mode. If enabled, we + * will stop at the immediate next breakpoint regardless of what thread it is in. */ +int rts_stop_next_breakpoint = 0; + +void rts_enableStopNextBreakpointAll(void) +{ + rts_stop_next_breakpoint = 1; +} + +void rts_disableStopNextBreakpointAll(void) +{ + rts_stop_next_breakpoint = 0; +} + +/* --------------------------------------------------------------------------- + * Enabling and disabling per-thread single step mode + * ------------------------------------------------------------------------ */ + +void rts_enableStopNextBreakpoint(StgPtr tso) +{ + ((StgTSO *)tso)->flags |= TSO_STOP_NEXT_BREAKPOINT; +} + +void rts_disableStopNextBreakpoint(StgPtr tso) +{ + ((StgTSO *)tso)->flags &= ~TSO_STOP_NEXT_BREAKPOINT; +} + +/* -------------------------------------------------------------------------- */ + #if defined(INTERP_STATS) #define N_CODES 128 @@ -1250,7 +1285,7 @@ run_BCO: int arg8_cc; #endif StgArrBytes *breakPoints; - int returning_from_break; + int returning_from_break, stop_next_breakpoint; // the io action to run at a breakpoint StgClosure *ioAction; @@ -1280,6 +1315,13 @@ run_BCO: returning_from_break = cap->r.rCurrentTSO->flags & TSO_STOPPED_ON_BREAKPOINT; + // check whether this thread is set to stop at the immediate next + // breakpoint -- either by the global `rts_stop_next_breakpoint` + // flag, or by the local `TSO_STOP_NEXT_BREAKPOINT` + stop_next_breakpoint = + rts_stop_next_breakpoint || + cap->r.rCurrentTSO->flags & TSO_STOP_NEXT_BREAKPOINT; + #if defined(PROFILING) cap->r.rCCCS = pushCostCentre(cap->r.rCCCS, (CostCentre*)BCO_LIT(arg8_cc)); @@ -1291,20 +1333,20 @@ run_BCO: { breakPoints = (StgArrBytes *) BCO_PTR(arg1_brk_array); - // stop the current thread if either the - // "rts_stop_next_breakpoint" flag is true OR if the - // ignore count for this particular breakpoint is zero + // stop the current thread if either `stop_next_breakpoint` is + // true OR if the ignore count for this particular breakpoint is zero StgInt ignore_count = ((StgInt*)breakPoints->payload)[arg6_tick_index]; - if (rts_stop_next_breakpoint == false && ignore_count > 0) + if (stop_next_breakpoint == false && ignore_count > 0) { // decrement and write back ignore count ((StgInt*)breakPoints->payload)[arg6_tick_index] = --ignore_count; } - else if (rts_stop_next_breakpoint == true || ignore_count == 0) + else if (stop_next_breakpoint == true || ignore_count == 0) { // make sure we don't automatically stop at the // next breakpoint - rts_stop_next_breakpoint = false; + rts_stop_next_breakpoint = 0; + cap->r.rCurrentTSO->flags &= ~TSO_STOP_NEXT_BREAKPOINT; // allocate memory for a new AP_STACK, enough to // store the top stack frame plus an ===================================== rts/Interpreter.h ===================================== @@ -11,3 +11,8 @@ RTS_PRIVATE Capability *interpretBCO (Capability* cap); void interp_startup ( void ); void interp_shutdown ( void ); + +void rts_enableStopNextBreakpointAll ( void ); +void rts_disableStopNextBreakpointAll ( void ); +void rts_enableStopNextBreakpoint ( StgPtr ); +void rts_disableStopNextBreakpoint ( StgPtr ); ===================================== rts/RtsSymbols.c ===================================== @@ -906,7 +906,10 @@ extern char **environ; SymI_HasProto(revertCAFs) \ SymI_HasProto(RtsFlags) \ SymI_NeedsDataProto(rts_breakpoint_io_action) \ - SymI_NeedsDataProto(rts_stop_next_breakpoint) \ + SymI_NeedsDataProto(rts_enableStopNextBreakpointAll) \ + SymI_NeedsDataProto(rts_disableStopNextBreakpointAll) \ + SymI_NeedsDataProto(rts_enableStopNextBreakpoint) \ + SymI_NeedsDataProto(rts_disableStopNextBreakpoint) \ SymI_NeedsDataProto(rts_stop_on_exception) \ SymI_HasProto(stopTimer) \ SymI_HasProto(n_capabilities) \ ===================================== rts/include/rts/Constants.h ===================================== @@ -328,6 +328,12 @@ */ #define TSO_ALLOC_LIMIT 256 +/* + * Enables step-in mode for this thread -- it will stop at the immediate next + * breakpoint found in this thread. + */ +#define TSO_STOP_NEXT_BREAKPOINT 512 + /* * The number of times we spin in a spin lock before yielding (see * #3758). To tune this value, use the benchmark in #3758: run the View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac7b34fd65dffa77a7c20e81511a6b05... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac7b34fd65dffa77a7c20e81511a6b05... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Rodrigo Mesquita (@alt-romes)