Rodrigo Mesquita pushed to branch wip/romes/step-out-5 at Glasgow Haskell Compiler / GHC

Commits:

6 changed files:

Changes:

  • compiler/GHC/ByteCode/Asm.hs
    ... ... @@ -858,7 +858,7 @@ assembleI platform i = case i of
    858 858
                                                       , Op np
    
    859 859
                                                       ]
    
    860 860
     
    
    861
    -  BRK_INTERNAL active -> emit_ bci_BRK_INTERNAL [SmallOp active]
    
    861
    +  BRK_ALTS active -> emit_ bci_BRK_ALTS [SmallOp active]
    
    862 862
     
    
    863 863
     #if MIN_VERSION_rts(1,0,3)
    
    864 864
       BCO_NAME name            -> do np <- lit1 (BCONPtrStr name)
    

  • compiler/GHC/ByteCode/Instr.hs
    ... ... @@ -272,9 +272,10 @@ data BCInstr
    272 272
                           !UnitId                -- breakpoint info module unit id
    
    273 273
                           !Word16                -- breakpoint info index
    
    274 274
                           (RemotePtr CostCentre)
    
    275
    -   -- An internal breakpoint should only be set by the compiler or RTS
    
    276
    -   -- See Note [BRK_INTERNAL]
    
    277
    -   | BRK_INTERNAL     !Word16 {- enabled? -}
    
    275
    +
    
    276
    +   -- An internal breakpoint for triggering a break on any case alternative
    
    277
    +   -- See Note [Debugger: BRK_ALTS]
    
    278
    +   | BRK_ALTS         !Word16 {- enabled? -}
    
    278 279
     
    
    279 280
     #if MIN_VERSION_rts(1,0,3)
    
    280 281
        -- | A "meta"-instruction for recording the name of a BCO for debugging purposes.
    
    ... ... @@ -471,7 +472,7 @@ instance Outputable BCInstr where
    471 472
                                    <+> text "<tick_module>" <+> text "<tick_module_unitid>" <+> ppr tickx
    
    472 473
                                    <+> text "<info_module>" <+> text "<info_module_unitid>" <+> ppr infox
    
    473 474
                                    <+> text "<cc>"
    
    474
    -   ppr (BRK_INTERNAL active) = text "BRK_INTERNAL" <+> ppr active
    
    475
    +   ppr (BRK_ALTS active)     = text "BRK_ALTS" <+> ppr active
    
    475 476
     #if MIN_VERSION_rts(1,0,3)
    
    476 477
        ppr (BCO_NAME nm)         = text "BCO_NAME" <+> text (show nm)
    
    477 478
     #endif
    
    ... ... @@ -597,7 +598,7 @@ bciStackUse OP_INDEX_ADDR{} = 0
    597 598
     
    
    598 599
     bciStackUse SWIZZLE{}             = 0
    
    599 600
     bciStackUse BRK_FUN{}             = 0
    
    600
    -bciStackUse BRK_INTERNAL{}        = 0
    
    601
    +bciStackUse BRK_ALTS{}            = 0
    
    601 602
     
    
    602 603
     -- These insns actually reduce stack use, but we need the high-tide level,
    
    603 604
     -- 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
    1372 1372
                | ubx_tuple_frame    = SLIDE 0 2 `consOL` alt_final0
    
    1373 1373
                | otherwise          = alt_final0
    
    1374 1374
              alt_final
    
    1375
    -          = BRK_INTERNAL 0 `consOL` alt_final1
    
    1375
    +           | gopt Opt_InsertBreakpoints (hsc_dflags hsc_env)
    
    1376
    +                                -- See Note [Debugger: BRK_ALTS]
    
    1377
    +                                = BRK_ALTS 0 `consOL` alt_final1
    
    1378
    +           | otherwise          = alt_final1
    
    1376 1379
     
    
    1377 1380
          add_bco_name <- shouldAddBcoName
    
    1378 1381
          let
    
    ... ... @@ -1392,6 +1395,37 @@ doCase d s p scrut bndr alts
    1392 1395
                       _     -> panic "schemeE(StgCase).push_alts"
    
    1393 1396
                 in return (PUSH_ALTS alt_bco scrut_rep `consOL` scrut_code)
    
    1394 1397
     
    
    1398
    +{-
    
    1399
    +Note [Debugger: BRK_ALTS]
    
    1400
    +~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1401
    +As described in Note [Debugger: Step-out] in rts/Interpreter.c, to implement
    
    1402
    +the stepping-out debugger feature we traverse the heap at runtime, identify
    
    1403
    +the continuation BCO, and explicitly enable that BCO's breakpoint thus ensuring
    
    1404
    +we stop exactly when we return to the continuation.
    
    1405
    +
    
    1406
    +However, a case continuation BCO (pushed by PUSH_ALTS), which computes what
    
    1407
    +case alternative BCO to take, never gets a user-facing breakpoint tick (BRK_FUN):
    
    1408
    +
    
    1409
    +  1) It's not useful to a user stepping through the program to always have a
    
    1410
    +  breakpoint after the scrutinee is evaluated but before the case alternative
    
    1411
    +  is selected. The associated source span would also be slightly awkward to choose.
    
    1412
    +
    
    1413
    +  2) It's not easy to add a source-tick before the case alternatives because in
    
    1414
    +  essentially all internal representations they are given as a list of Alts
    
    1415
    +  rather than an expression.
    
    1416
    +
    
    1417
    +To provide the debugger a way to enable at runtime the case continuation
    
    1418
    +breakpoints regardless, we introduce at the start of every PUSH_ALTS BCO a
    
    1419
    +BRK_ALTS instruction.
    
    1420
    +
    
    1421
    +The BRK_ALTS instruction, if enabled (by its single arg), ensures we stop at
    
    1422
    +the breakpoint heading the case alternative we take. Under the hood, this means
    
    1423
    +that when BRK_ALTS is enabled we set TSO_STOP_NEXT_BREAKPOINT just before
    
    1424
    +selecting the alternative.
    
    1425
    +
    
    1426
    +It's important that BRK_ALTS (just like BRK_FUN) is the first instruction of
    
    1427
    +the BCO, since that's where the debugger will look to enable it at runtime.
    
    1428
    +-}
    
    1395 1429
     
    
    1396 1430
     -- -----------------------------------------------------------------------------
    
    1397 1431
     -- Deal with tuples
    

  • rts/Disassembler.c
    ... ... @@ -94,8 +94,8 @@ disInstr ( StgBCO *bco, int pc )
    94 94
              debugBelch("\n");
    
    95 95
              pc += 6;
    
    96 96
              break;
    
    97
    -      case bci_BRK_INTERNAL:
    
    98
    -         debugBelch ("BRK_INTERNAL %d\n", BCO_NEXT);
    
    97
    +      case bci_BRK_ALTS:
    
    98
    +         debugBelch ("BRK_ALTS %d\n", BCO_NEXT);
    
    99 99
              break;
    
    100 100
           case bci_SWIZZLE: {
    
    101 101
              W_     stkoff = BCO_GET_LARGE_ARG;
    

  • rts/Interpreter.c
    ... ... @@ -643,10 +643,12 @@ interpretBCO (Capability* cap)
    643 643
                 // ACTIVATE the breakpoint by tick index
    
    644 644
                 ((StgInt*)breakPoints->payload)[tick_index] = 0;
    
    645 645
             }
    
    646
    -        else if ((bco_instrs[0] & 0xFF) == bci_BRK_INTERNAL) {
    
    646
    +        else if ((bco_instrs[0] & 0xFF) == bci_BRK_ALTS) {
    
    647 647
                 // ACTIVATE BRK_ALTS by setting its only argument to ON
    
    648 648
                 bco_instrs[1] = 1;
    
    649 649
             }
    
    650
    +        // else: if there is no BRK instruction perhaps we should keep
    
    651
    +        // traversing; that said, the continuation should always have a BRK
    
    650 652
           }
    
    651 653
           else /* type == STOP_FRAME */ {
    
    652 654
             /* No continuation frame to further stop at: Nothing to do */
    
    ... ... @@ -1588,14 +1590,11 @@ run_BCO:
    1588 1590
                 goto nextInsn;
    
    1589 1591
             }
    
    1590 1592
     
    
    1591
    -        case bci_BRK_INTERNAL:
    
    1593
    +        /* See Note [Debugger: BRK_ALTS] */
    
    1594
    +        case bci_BRK_ALTS:
    
    1592 1595
             {
    
    1593
    -          printf("BREAK INTERNAL\n");
    
    1594 1596
               StgWord16 active = BCO_NEXT;
    
    1595
    -          printf("BREAK INTERNAL: %d\n", active);
    
    1596 1597
               if (active) {
    
    1597
    -            printf("BREAK INTERNAL is active\n");
    
    1598
    -            // Break on next!
    
    1599 1598
                 cap->r.rCurrentTSO->flags |= TSO_STOP_NEXT_BREAKPOINT;
    
    1600 1599
               }
    
    1601 1600
     
    

  • rts/include/rts/Bytecodes.h
    ... ... @@ -214,7 +214,7 @@
    214 214
     #define bci_OP_INDEX_ADDR_32           242
    
    215 215
     #define bci_OP_INDEX_ADDR_64           243
    
    216 216
     
    
    217
    -#define bci_BRK_INTERNAL               244
    
    217
    +#define bci_BRK_ALTS                   244
    
    218 218
     
    
    219 219
     
    
    220 220
     /* If you need to go past 255 then you will run into the flags */