Rodrigo Mesquita pushed to branch wip/romes/step-out-5 at Glasgow Haskell Compiler / GHC
Commits:
2d7995dc by Rodrigo Mesquita at 2025-06-16T12:05:34+01:00
BRK_ALTS BCO
- - - - -
6 changed files:
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/StgToByteCode.hs
- rts/Disassembler.c
- rts/Interpreter.c
- rts/include/rts/Bytecodes.h
Changes:
=====================================
compiler/GHC/ByteCode/Asm.hs
=====================================
@@ -858,7 +858,7 @@ assembleI platform i = case i of
, Op np
]
- BRK_INTERNAL active -> emit_ bci_BRK_INTERNAL [SmallOp active]
+ BRK_ALTS active -> emit_ bci_BRK_ALTS [SmallOp active]
#if MIN_VERSION_rts(1,0,3)
BCO_NAME name -> do np <- lit1 (BCONPtrStr name)
=====================================
compiler/GHC/ByteCode/Instr.hs
=====================================
@@ -272,9 +272,10 @@ data BCInstr
!UnitId -- breakpoint info module unit id
!Word16 -- breakpoint info index
(RemotePtr CostCentre)
- -- An internal breakpoint should only be set by the compiler or RTS
- -- See Note [BRK_INTERNAL]
- | BRK_INTERNAL !Word16 {- enabled? -}
+
+ -- An internal breakpoint for triggering a break on any case alternative
+ -- See Note [Debugger: BRK_ALTS]
+ | BRK_ALTS !Word16 {- enabled? -}
#if MIN_VERSION_rts(1,0,3)
-- | A "meta"-instruction for recording the name of a BCO for debugging purposes.
@@ -471,7 +472,7 @@ instance Outputable BCInstr where
<+> text "" <+> text "" <+> ppr tickx
<+> text "" <+> text "" <+> ppr infox
<+> text "<cc>"
- ppr (BRK_INTERNAL active) = text "BRK_INTERNAL" <+> ppr active
+ ppr (BRK_ALTS active) = text "BRK_ALTS" <+> ppr active
#if MIN_VERSION_rts(1,0,3)
ppr (BCO_NAME nm) = text "BCO_NAME" <+> text (show nm)
#endif
@@ -597,7 +598,7 @@ bciStackUse OP_INDEX_ADDR{} = 0
bciStackUse SWIZZLE{} = 0
bciStackUse BRK_FUN{} = 0
-bciStackUse BRK_INTERNAL{} = 0
+bciStackUse BRK_ALTS{} = 0
-- These insns actually reduce stack use, but we need the high-tide level,
-- so can't use this info. Not that it matters much.
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -1372,7 +1372,10 @@ doCase d s p scrut bndr alts
| ubx_tuple_frame = SLIDE 0 2 `consOL` alt_final0
| otherwise = alt_final0
alt_final
- = BRK_INTERNAL 0 `consOL` alt_final1
+ | gopt Opt_InsertBreakpoints (hsc_dflags hsc_env)
+ -- See Note [Debugger: BRK_ALTS]
+ = BRK_ALTS 0 `consOL` alt_final1
+ | otherwise = alt_final1
add_bco_name <- shouldAddBcoName
let
@@ -1392,6 +1395,37 @@ doCase d s p scrut bndr alts
_ -> panic "schemeE(StgCase).push_alts"
in return (PUSH_ALTS alt_bco scrut_rep `consOL` scrut_code)
+{-
+Note [Debugger: BRK_ALTS]
+~~~~~~~~~~~~~~~~~~~~~~~~~
+As described in Note [Debugger: Step-out] in rts/Interpreter.c, to implement
+the stepping-out debugger feature we traverse the heap at runtime, identify
+the continuation BCO, and explicitly enable that BCO's breakpoint thus ensuring
+we stop exactly when we return to the continuation.
+
+However, a case continuation BCO (pushed by PUSH_ALTS), which computes what
+case alternative BCO to take, never gets a user-facing breakpoint tick (BRK_FUN):
+
+ 1) It's not useful to a user stepping through the program to always have a
+ breakpoint after the scrutinee is evaluated but before the case alternative
+ is selected. The associated source span would also be slightly awkward to choose.
+
+ 2) It's not easy to add a source-tick before the case alternatives because in
+ essentially all internal representations they are given as a list of Alts
+ rather than an expression.
+
+To provide the debugger a way to enable at runtime the case continuation
+breakpoints regardless, we introduce at the start of every PUSH_ALTS BCO a
+BRK_ALTS instruction.
+
+The BRK_ALTS instruction, if enabled (by its single arg), ensures we stop at
+the breakpoint heading the case alternative we take. Under the hood, this means
+that when BRK_ALTS is enabled we set TSO_STOP_NEXT_BREAKPOINT just before
+selecting the alternative.
+
+It's important that BRK_ALTS (just like BRK_FUN) is the first instruction of
+the BCO, since that's where the debugger will look to enable it at runtime.
+-}
-- -----------------------------------------------------------------------------
-- Deal with tuples
=====================================
rts/Disassembler.c
=====================================
@@ -94,8 +94,8 @@ disInstr ( StgBCO *bco, int pc )
debugBelch("\n");
pc += 6;
break;
- case bci_BRK_INTERNAL:
- debugBelch ("BRK_INTERNAL %d\n", BCO_NEXT);
+ case bci_BRK_ALTS:
+ debugBelch ("BRK_ALTS %d\n", BCO_NEXT);
break;
case bci_SWIZZLE: {
W_ stkoff = BCO_GET_LARGE_ARG;
=====================================
rts/Interpreter.c
=====================================
@@ -643,10 +643,12 @@ interpretBCO (Capability* cap)
// ACTIVATE the breakpoint by tick index
((StgInt*)breakPoints->payload)[tick_index] = 0;
}
- else if ((bco_instrs[0] & 0xFF) == bci_BRK_INTERNAL) {
+ else if ((bco_instrs[0] & 0xFF) == bci_BRK_ALTS) {
// ACTIVATE BRK_ALTS by setting its only argument to ON
bco_instrs[1] = 1;
}
+ // else: if there is no BRK instruction perhaps we should keep
+ // traversing; that said, the continuation should always have a BRK
}
else /* type == STOP_FRAME */ {
/* No continuation frame to further stop at: Nothing to do */
@@ -1588,14 +1590,11 @@ run_BCO:
goto nextInsn;
}
- case bci_BRK_INTERNAL:
+ /* See Note [Debugger: BRK_ALTS] */
+ case bci_BRK_ALTS:
{
- printf("BREAK INTERNAL\n");
StgWord16 active = BCO_NEXT;
- printf("BREAK INTERNAL: %d\n", active);
if (active) {
- printf("BREAK INTERNAL is active\n");
- // Break on next!
cap->r.rCurrentTSO->flags |= TSO_STOP_NEXT_BREAKPOINT;
}
=====================================
rts/include/rts/Bytecodes.h
=====================================
@@ -214,7 +214,7 @@
#define bci_OP_INDEX_ADDR_32 242
#define bci_OP_INDEX_ADDR_64 243
-#define bci_BRK_INTERNAL 244
+#define bci_BRK_ALTS 244
/* If you need to go past 255 then you will run into the flags */
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d7995dca4abd94a3f36a14e8262f67a...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d7995dca4abd94a3f36a14e8262f67a...
You're receiving this email because of your account on gitlab.haskell.org.