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

Commits:

13 changed files:

Changes:

  • compiler/GHC/ByteCode/Breakpoints.hs
    ... ... @@ -177,15 +177,17 @@ data CgBreakInfo
    177 177
          -- necessarily the same: See Note [Breakpoint identifiers].
    
    178 178
          --
    
    179 179
          -- If there is no original tick identifier (that is, the breakpoint was
    
    180
    -     -- created during code generation), instead refer directly to the SrcSpan
    
    181
    -     -- we want to use for it.
    
    180
    +     -- created during code generation), we re-use the BreakpointId of something else.
    
    181
    +     -- It would also be reasonable to have an @Either something BreakpointId@
    
    182
    +     -- for @cgb_tick_id@, but currently we can always re-use a source-level BreakpointId.
    
    183
    +     -- In the case of step-out, see Note [Debugger: Stepout internal break locs]
    
    182 184
        }
    
    183 185
     -- See Note [Syncing breakpoint info] in GHC.Runtime.Eval
    
    184 186
     
    
    185 187
     -- | Breakpoints created during code generation don't have a source-level tick
    
    186
    --- location. Instead, we come up with one ourselves.
    
    187
    -newtype InternalBreakLoc = InternalBreakLoc SrcSpan
    
    188
    -  deriving newtype (Eq, Show, NFData, Outputable)
    
    188
    +-- location. Instead, we re-use an existing one.
    
    189
    +newtype InternalBreakLoc = InternalBreakLoc { internalBreakLoc :: BreakpointId }
    
    190
    +  deriving newtype (Eq, NFData, Outputable)
    
    189 191
     
    
    190 192
     -- | Get an internal breakpoint info by 'InternalBreakpointId'
    
    191 193
     getInternalBreak :: InternalBreakpointId -> InternalModBreaks -> CgBreakInfo
    
    ... ... @@ -207,36 +209,34 @@ assert_modules_match ibi_mod imbs_mod =
    207 209
     
    
    208 210
     -- | Get the source module and tick index for this breakpoint
    
    209 211
     -- (as opposed to the module where this breakpoint occurs, which is in 'InternalBreakpointId')
    
    210
    -getBreakSourceId :: InternalBreakpointId -> InternalModBreaks -> Either InternalBreakLoc BreakpointId
    
    212
    +getBreakSourceId :: InternalBreakpointId -> InternalModBreaks -> BreakpointId
    
    211 213
     getBreakSourceId (InternalBreakpointId ibi_mod ibi_ix) imbs =
    
    212 214
       assert_modules_match ibi_mod (imodBreaks_module imbs) $
    
    213 215
         let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
    
    214
    -     in cgb_tick_id cgb
    
    216
    +     in either internalBreakLoc id (cgb_tick_id cgb)
    
    215 217
     
    
    216 218
     -- | Get the source module for this breakpoint (where the breakpoint is defined)
    
    217 219
     getBreakSourceMod :: InternalBreakpointId -> InternalModBreaks -> Module
    
    218 220
     getBreakSourceMod (InternalBreakpointId ibi_mod ibi_ix) imbs =
    
    219 221
       assert_modules_match ibi_mod (imodBreaks_module imbs) $
    
    220 222
         let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
    
    221
    -     in case cgb_tick_id cgb of
    
    222
    -      Left InternalBreakLoc{} -> imodBreaks_module imbs
    
    223
    -      Right BreakpointId{bi_tick_mod} -> bi_tick_mod
    
    223
    +     in either (bi_tick_mod . internalBreakLoc) bi_tick_mod (cgb_tick_id cgb)
    
    224 224
     
    
    225 225
     -- | Get the source span for this breakpoint
    
    226 226
     getBreakLoc :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO SrcSpan
    
    227
    -getBreakLoc = getBreakXXX modBreaks_locs (\(InternalBreakLoc x) -> x)
    
    227
    +getBreakLoc = getBreakXXX modBreaks_locs
    
    228 228
     
    
    229 229
     -- | Get the vars for this breakpoint
    
    230 230
     getBreakVars :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [OccName]
    
    231
    -getBreakVars = getBreakXXX modBreaks_vars (const [])
    
    231
    +getBreakVars = getBreakXXX modBreaks_vars
    
    232 232
     
    
    233 233
     -- | Get the decls for this breakpoint
    
    234 234
     getBreakDecls :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [String]
    
    235
    -getBreakDecls = getBreakXXX modBreaks_decls (const [])
    
    235
    +getBreakDecls = getBreakXXX modBreaks_decls
    
    236 236
     
    
    237 237
     -- | Get the decls for this breakpoint
    
    238
    -getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO (Maybe (String, String))
    
    239
    -getBreakCCS = getBreakXXX (fmap Just . modBreaks_ccs) (const Nothing)
    
    238
    +getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO ((String, String))
    
    239
    +getBreakCCS = getBreakXXX modBreaks_ccs
    
    240 240
     
    
    241 241
     -- | Internal utility to access a ModBreaks field at a particular breakpoint index
    
    242 242
     --
    
    ... ... @@ -253,12 +253,12 @@ getBreakCCS = getBreakXXX (fmap Just . modBreaks_ccs) (const Nothing)
    253 253
     --
    
    254 254
     -- To avoid cyclic dependencies, we instead receive a function that looks up
    
    255 255
     -- the 'ModBreaks' given a 'Module'
    
    256
    -getBreakXXX :: (ModBreaks -> Array BreakTickIndex a) -> (InternalBreakLoc -> a) -> (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO a
    
    257
    -getBreakXXX view viewInternal lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
    
    256
    +getBreakXXX :: (ModBreaks -> Array BreakTickIndex a) -> (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO a
    
    257
    +getBreakXXX view lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
    
    258 258
       assert_modules_match ibi_mod (imodBreaks_module imbs) $ do
    
    259 259
         let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
    
    260
    -    case cgb_tick_id cgb of
    
    261
    -      Right BreakpointId{bi_tick_mod, bi_tick_index}
    
    260
    +    case either internalBreakLoc id (cgb_tick_id cgb) of
    
    261
    +      BreakpointId{bi_tick_mod, bi_tick_index}
    
    262 262
             | bi_tick_mod == ibi_mod
    
    263 263
             -> do
    
    264 264
               let these_mbs = imodBreaks_modBreaks imbs
    
    ... ... @@ -267,8 +267,6 @@ getBreakXXX view viewInternal lookupModule (InternalBreakpointId ibi_mod ibi_ix)
    267 267
             -> do
    
    268 268
               other_mbs <- lookupModule bi_tick_mod
    
    269 269
               return $ view other_mbs ! bi_tick_index
    
    270
    -      Left l ->
    
    271
    -          return $ viewInternal l
    
    272 270
     
    
    273 271
     --------------------------------------------------------------------------------
    
    274 272
     -- Instances
    

  • compiler/GHC/Linker/Loader.hs
    ... ... @@ -1712,10 +1712,8 @@ allocateCCS interp ce mbss
    1712 1712
                   let count = maybe 0 ((+1) . fst) $ IM.lookupMax imodBreaks_breakInfo
    
    1713 1713
                   let ccs = IM.map
    
    1714 1714
                         (\info ->
    
    1715
    -                      case cgb_tick_id info of
    
    1716
    -                        Right bi -> fromMaybe (toRemotePtr nullPtr)
    
    1717
    -                          (M.lookup bi ccss)
    
    1718
    -                        Left InternalBreakLoc{} -> toRemotePtr nullPtr
    
    1715
    +                        fromMaybe (toRemotePtr nullPtr)
    
    1716
    +                          (M.lookup (either internalBreakLoc id (cgb_tick_id info)) ccss)
    
    1719 1717
                         )
    
    1720 1718
                         imodBreaks_breakInfo
    
    1721 1719
                   assertPpr (count == length ccs)
    

  • compiler/GHC/Runtime/Debugger/Breakpoints.hs
    ... ... @@ -257,6 +257,8 @@ mkBreakpointOccurrences = do
    257 257
                 Right (BreakpointId tick_mod tick_ix)
    
    258 258
                   -> extendModuleEnvWith (IntMap.unionWith (S.<>)) bmp tick_mod (IntMap.singleton tick_ix [ibi])
    
    259 259
                 Left _
    
    260
    +              -- Do not include internal breakpoints in the visible breakpoint
    
    261
    +              -- occurrences!
    
    260 262
                   -> bmp
    
    261 263
             ) bmp0 (imodBreaks_breakInfo ibrks)
    
    262 264
     
    

  • compiler/GHC/StgToByteCode.hs
    ... ... @@ -63,7 +63,7 @@ import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, idPrimRepU,
    63 63
                                   assertNonVoidIds, assertNonVoidStgArgs )
    
    64 64
     import GHC.StgToCmm.Layout
    
    65 65
     import GHC.Runtime.Heap.Layout hiding (WordOff, ByteOff, wordsToBytes)
    
    66
    -import GHC.Runtime.Interpreter ( interpreterProfiled, readIModModBreaks )
    
    66
    +import GHC.Runtime.Interpreter ( interpreterProfiled )
    
    67 67
     import GHC.Data.Bitmap
    
    68 68
     import GHC.Data.FlatBag as FlatBag
    
    69 69
     import GHC.Data.OrdList
    
    ... ... @@ -99,7 +99,7 @@ import GHC.CoreToIface
    99 99
     import Control.Monad.IO.Class
    
    100 100
     import Control.Monad.Trans.Reader (ReaderT(..))
    
    101 101
     import Control.Monad.Trans.State  (StateT(..))
    
    102
    -import Data.Array ((!))
    
    102
    +import Data.Bifunctor (Bifunctor(..))
    
    103 103
     
    
    104 104
     -- -----------------------------------------------------------------------------
    
    105 105
     -- Generating byte code for a complete module
    
    ... ... @@ -402,11 +402,16 @@ schemeER_wrk d p (StgTick bp@(Breakpoint tick_ty tick_id fvs) rhs) = do
    402 402
       -- See Note [Debugger: Stepout internal break locs]
    
    403 403
       code <- withBreakTick bp $ schemeE d 0 p rhs
    
    404 404
     
    
    405
    -  let idOffSets = getVarOffSets platform d p fvs
    
    405
    +  -- As per Note [Stack layout when entering run_BCO], the breakpoint AP_STACK
    
    406
    +  -- as we yield from the interpreter is headed by a stg_apply_interp + BCO to be a valid stack.
    
    407
    +  -- Therefore, the var offsets are offset by 2 words
    
    408
    +  let idOffSets = map (fmap (second (+2))) $
    
    409
    +                  getVarOffSets platform d p fvs
    
    406 410
           ty_vars   = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
    
    407 411
           toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
    
    408 412
           toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
    
    409
    -      breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Right tick_id)
    
    413
    +      breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty
    
    414
    +                    (Right tick_id)
    
    410 415
     
    
    411 416
       mibi <- newBreakInfo breakInfo
    
    412 417
     
    
    ... ... @@ -416,21 +421,15 @@ schemeER_wrk d p (StgTick bp@(Breakpoint tick_ty tick_id fvs) rhs) = do
    416 421
     
    
    417 422
     schemeER_wrk d p rhs = schemeE d 0 p rhs
    
    418 423
     
    
    424
    +-- | Get the offset in words into this breakpoint's AP_STACK which contains the matching Id
    
    419 425
     getVarOffSets :: Platform -> StackDepth -> BCEnv -> [Id] -> [Maybe (Id, WordOff)]
    
    420 426
     getVarOffSets platform depth env = map getOffSet
    
    421 427
       where
    
    422 428
         getOffSet id = case lookupBCEnv_maybe id env of
    
    423
    -        Nothing     -> Nothing
    
    424
    -        Just offset ->
    
    425
    -            -- michalt: I'm not entirely sure why we need the stack
    
    426
    -            -- adjustment by 2 here. I initially thought that there's
    
    427
    -            -- something off with getIdValFromApStack (the only user of this
    
    428
    -            -- value), but it looks ok to me. My current hypothesis is that
    
    429
    -            -- this "adjustment" is needed due to stack manipulation for
    
    430
    -            -- BRK_FUN in Interpreter.c In any case, this is used only when
    
    431
    -            -- we trigger a breakpoint.
    
    432
    -            let !var_depth_ws = bytesToWords platform (depth - offset) + 2
    
    433
    -            in Just (id, var_depth_ws)
    
    429
    +      Nothing     -> Nothing
    
    430
    +      Just offset ->
    
    431
    +          let !var_depth_ws = bytesToWords platform (depth - offset)
    
    432
    +          in Just (id, var_depth_ws)
    
    434 433
     
    
    435 434
     fvsToEnv :: BCEnv -> CgStgRhs -> [Id]
    
    436 435
     -- Takes the free variables of a right-hand side, and
    
    ... ... @@ -1141,10 +1140,17 @@ doCase d s p scrut bndr alts
    1141 1140
             -- When an alt is entered, it assumes the returned value is
    
    1142 1141
             -- on top of the itbl; see Note [Return convention for non-tuple values]
    
    1143 1142
             -- for details.
    
    1144
    -        ret_frame_size_w :: WordOff
    
    1145
    -        ret_frame_size_w | ubx_tuple_frame =
    
    1146
    -                             if profiling then 5 else 4
    
    1147
    -                         | otherwise = 2
    
    1143
    +        ctoi_frame_header_w :: WordOff
    
    1144
    +        ctoi_frame_header_w
    
    1145
    +          | ubx_tuple_frame =
    
    1146
    +              if profiling then 5 else 4
    
    1147
    +          | otherwise = 2
    
    1148
    +
    
    1149
    +        -- The size of the ret_*_info frame header, whose frame returns the
    
    1150
    +        -- value to the case continuation frame (ctoi_*_info)
    
    1151
    +        ret_info_header_w :: WordOff
    
    1152
    +          | ubx_tuple_frame = 3
    
    1153
    +          | otherwise = 1
    
    1148 1154
     
    
    1149 1155
             -- The stack space used to save/restore the CCCS when profiling
    
    1150 1156
             save_ccs_size_b | profiling &&
    
    ... ... @@ -1319,12 +1325,10 @@ doCase d s p scrut bndr alts
    1319 1325
          let
    
    1320 1326
     
    
    1321 1327
              -- drop the stg_ctoi_*_info header...
    
    1322
    -         alt_final1 = SLIDE bndr_size ret_frame_size_w `consOL` alt_final0
    
    1328
    +         alt_final1 = SLIDE bndr_size ctoi_frame_header_w `consOL` alt_final0
    
    1323 1329
     
    
    1324 1330
              -- after dropping the stg_ret_*_info header
    
    1325
    -         alt_final2
    
    1326
    -           | ubx_tuple_frame    = SLIDE 0 3 `consOL` alt_final1
    
    1327
    -           | otherwise          = SLIDE 0 1 `consOL` alt_final1
    
    1331
    +         alt_final2 = SLIDE 0 ret_info_header_w `consOL` alt_final1
    
    1328 1332
     
    
    1329 1333
          -- When entering a case continuation BCO, the stack is always headed
    
    1330 1334
          -- by the stg_ret frame and the stg_ctoi frame that returned to it.
    
    ... ... @@ -1341,14 +1345,21 @@ doCase d s p scrut bndr alts
    1341 1345
              -- continuation BCO, for step-out.
    
    1342 1346
              -- See Note [Debugger: Stepout internal break locs]
    
    1343 1347
              -> do
    
    1344
    -          internal_tick_loc <- makeCaseInternalBreakLoc tick_id
    
    1345 1348
     
    
    1346
    -          -- same fvs available in the case expression are available in the case continuation
    
    1347
    -          let idOffSets = getVarOffSets platform d p fvs
    
    1349
    +          -- same fvs available in the surrounding tick are available in the case continuation
    
    1350
    +
    
    1351
    +          -- The variable offsets into the yielded AP_STACK are adjusted
    
    1352
    +          -- differently because a case continuation AP_STACK has the
    
    1353
    +          -- additional stg_ret and stg_ctoi frame headers
    
    1354
    +          -- (as per Note [Stack layout when entering run_BCO]):
    
    1355
    +          let firstVarOff = ret_info_header_w+bndr_size+ctoi_frame_header_w
    
    1356
    +              idOffSets = map (fmap (second (+firstVarOff))) $
    
    1357
    +                          getVarOffSets platform d p fvs
    
    1348 1358
                   ty_vars   = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
    
    1349 1359
                   toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
    
    1350 1360
                   toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
    
    1351
    -              breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Left internal_tick_loc)
    
    1361
    +              breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty
    
    1362
    +                            (Left (InternalBreakLoc tick_id))
    
    1352 1363
     
    
    1353 1364
               mibi <- newBreakInfo breakInfo
    
    1354 1365
               return $ case mibi of
    
    ... ... @@ -1361,8 +1372,8 @@ doCase d s p scrut bndr alts
    1361 1372
              alt_bco_name = getName bndr
    
    1362 1373
              alt_bco = mkProtoBCO platform add_bco_name alt_bco_name alt_final (Left alts)
    
    1363 1374
                            0{-no arity-} bitmap_size bitmap True{-is alts-}
    
    1364
    -     scrut_code <- schemeE (d + wordsToBytes platform ret_frame_size_w + save_ccs_size_b)
    
    1365
    -                           (d + wordsToBytes platform ret_frame_size_w + save_ccs_size_b)
    
    1375
    +     scrut_code <- schemeE (d + wordsToBytes platform ctoi_frame_header_w + save_ccs_size_b)
    
    1376
    +                           (d + wordsToBytes platform ctoi_frame_header_w + save_ccs_size_b)
    
    1366 1377
                                p scrut
    
    1367 1378
          if ubx_tuple_frame
    
    1368 1379
            then do let tuple_bco = tupleBCO platform call_info args_offsets
    
    ... ... @@ -1374,25 +1385,6 @@ doCase d s p scrut bndr alts
    1374 1385
                       _     -> panic "schemeE(StgCase).push_alts"
    
    1375 1386
                 in return (PUSH_ALTS alt_bco scrut_rep `consOL` scrut_code)
    
    1376 1387
     
    
    1377
    --- | Come up with an 'InternalBreakLoc' from the location of the given 'BreakpointId'.
    
    1378
    --- See also Note [Debugger: Stepout internal break locs]
    
    1379
    -makeCaseInternalBreakLoc :: BreakpointId -> BcM InternalBreakLoc
    
    1380
    -makeCaseInternalBreakLoc bid = do
    
    1381
    -  hug         <- hsc_HUG <$> getHscEnv
    
    1382
    -  curr_mod    <- getCurrentModule
    
    1383
    -  mb_mod_brks <- getCurrentModBreaks
    
    1384
    -
    
    1385
    -  InternalBreakLoc <$> case bid of
    
    1386
    -    BreakpointId{bi_tick_mod, bi_tick_index}
    
    1387
    -      | bi_tick_mod == curr_mod
    
    1388
    -      , Just these_mbs <- mb_mod_brks
    
    1389
    -      -> do
    
    1390
    -        return $ modBreaks_locs these_mbs ! bi_tick_index
    
    1391
    -      | otherwise
    
    1392
    -      -> do
    
    1393
    -        other_mbs <- liftIO $ readIModModBreaks hug bi_tick_mod
    
    1394
    -        return $ modBreaks_locs other_mbs ! bi_tick_index
    
    1395
    -
    
    1396 1388
     {-
    
    1397 1389
     Note [Debugger: Stepout internal break locs]
    
    1398 1390
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    ... ... @@ -1438,6 +1430,8 @@ always have a relevant breakpoint location:
    1438 1430
         - So the source location will point to the thing you've just stepped
    
    1439 1431
           out of
    
    1440 1432
     
    
    1433
    +    - The variables available are the same as the ones bound just before entering
    
    1434
    +
    
    1441 1435
         - Doing :step-local from there will put you on the selected
    
    1442 1436
           alternative (which at the source level may also be the e.g. next
    
    1443 1437
           line in a do-block)
    
    ... ... @@ -2758,9 +2752,6 @@ newBreakInfo info = BcM $ \env st -> do
    2758 2752
     getCurrentModule :: BcM Module
    
    2759 2753
     getCurrentModule = BcM $ \env st -> return (bcm_module env, st)
    
    2760 2754
     
    
    2761
    -getCurrentModBreaks :: BcM (Maybe ModBreaks)
    
    2762
    -getCurrentModBreaks = BcM $ \env st -> return (modBreaks env, st)
    
    2763
    -
    
    2764 2755
     withBreakTick :: StgTickish -> BcM a -> BcM a
    
    2765 2756
     withBreakTick bp (BcM act) = BcM $ \env st ->
    
    2766 2757
       act env{last_bp_tick=Just bp} st
    

  • ghc/GHCi/UI.hs
    ... ... @@ -1621,7 +1621,7 @@ toBreakIdAndLocation (Just inf) = do
    1621 1621
       brks <- liftIO $ readIModBreaks hug inf
    
    1622 1622
       let bi = getBreakSourceId inf brks
    
    1623 1623
       return $ listToMaybe [ id_loc | id_loc@(_,loc) <- IntMap.assocs (breaks st),
    
    1624
    -                                  Right (breakId loc) == bi ]
    
    1624
    +                                  breakId loc == bi ]
    
    1625 1625
     
    
    1626 1626
     printStoppedAtBreakInfo :: GHC.GhcMonad m => Resume -> [Name] -> m ()
    
    1627 1627
     printStoppedAtBreakInfo res names = do
    

  • testsuite/tests/ghci.debugger/scripts/T26042b.script
    ... ... @@ -7,12 +7,15 @@ main
    7 7
     -- stepout of foo True to caller (ie bar)
    
    8 8
     :stepout
    
    9 9
     :list
    
    10
    +:show bindings
    
    10 11
     -- stepout of bar (to branch of foo False, where bar was called)
    
    11 12
     :stepout
    
    12 13
     :list
    
    14
    +:show bindings
    
    13 15
     -- stepout to right after the call to foo False in main
    
    14 16
     :stepout
    
    15 17
     :list
    
    18
    +:show bindings
    
    16 19
     
    
    17 20
     -- done
    
    18 21
     :continue

  • testsuite/tests/ghci.debugger/scripts/T26042b.stdout
    ... ... @@ -8,7 +8,7 @@ _result ::
    8 8
     10  foo True  i = return i
    
    9 9
                       ^^^^^^^^
    
    10 10
     11  foo False _ = do
    
    11
    -Stopped in Main., T26042b.hs:20:3-17
    
    11
    +Stopped in Main.bar, T26042b.hs:20:3-17
    
    12 12
     _result ::
    
    13 13
       GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    14 14
       -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    ... ... @@ -17,7 +17,11 @@ _result ::
    17 17
     20    y <- foo True t
    
    18 18
           ^^^^^^^^^^^^^^^
    
    19 19
     21    return y
    
    20
    -Stopped in Main., T26042b.hs:14:3-18
    
    20
    +_result ::
    
    21
    +  GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    22
    +  -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    23
    +        Int #) = _
    
    24
    +Stopped in Main.foo, T26042b.hs:14:3-18
    
    21 25
     _result ::
    
    22 26
       GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    23 27
       -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    ... ... @@ -26,7 +30,11 @@ _result ::
    26 30
     14    n <- bar (x + y)
    
    27 31
           ^^^^^^^^^^^^^^^^
    
    28 32
     15    return n
    
    29
    -Stopped in Main., T26042b.hs:5:3-26
    
    33
    +_result ::
    
    34
    +  GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    35
    +  -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    36
    +        Int #) = _
    
    37
    +Stopped in Main.main, T26042b.hs:5:3-26
    
    30 38
     _result ::
    
    31 39
       GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    32 40
       -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    ... ... @@ -35,5 +43,9 @@ _result ::
    35 43
     5    a <- foo False undefined
    
    36 44
          ^^^^^^^^^^^^^^^^^^^^^^^^
    
    37 45
     6    print a
    
    46
    +_result ::
    
    47
    +  GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    48
    +  -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    
    49
    +        () #) = _
    
    38 50
     14
    
    39 51
     14

  • testsuite/tests/ghci.debugger/scripts/T26042c.stdout
    ... ... @@ -8,7 +8,7 @@ _result ::
    8 8
     10  foo True  i = return i
    
    9 9
                       ^^^^^^^^
    
    10 10
     11  foo False _ = do
    
    11
    -Stopped in Main., T26042c.hs:5:3-26
    
    11
    +Stopped in Main.main, T26042c.hs:5:3-26
    
    12 12
     _result ::
    
    13 13
       GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    14 14
       -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    

  • testsuite/tests/ghci.debugger/scripts/T26042d2.stdout
    ... ... @@ -11,7 +11,7 @@ _result ::
    11 11
     12    putStrLn "hello2.2"
    
    12 12
     hello2.1
    
    13 13
     hello2.2
    
    14
    -Stopped in Main., T26042d2.hs:6:3
    
    14
    +Stopped in Main.main, T26042d2.hs:6:3
    
    15 15
     _result ::
    
    16 16
       GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld
    
    17 17
       -> (# GHC.Internal.Prim.State# GHC.Internal.Prim.RealWorld,
    

  • testsuite/tests/ghci.debugger/scripts/T26042e.stdout
    ... ... @@ -7,7 +7,7 @@ y :: [a1] -> Int = _
    7 7
     11    let !z = y x
    
    8 8
           ^^^^^^^^^^^^
    
    9 9
     12    let !t = y ['b']
    
    10
    -Stopped in T7., T26042e.hs:18:3-17
    
    10
    +Stopped in T7.main, T26042e.hs:18:3-17
    
    11 11
     _result :: IO () = _
    
    12 12
     17  main = do
    
    13 13
     18    let !(x, y) = a
    

  • testsuite/tests/ghci.debugger/scripts/T26042f.script
    ... ... @@ -4,10 +4,12 @@ top
    4 4
     :list
    
    5 5
     -- out of t
    
    6 6
     :stepout
    
    7
    +:show bindings
    
    7 8
     :list
    
    8 9
     -- out of g
    
    9 10
     :stepout
    
    10 11
     :list
    
    12
    +:show bindings
    
    11 13
     -- out of f
    
    12 14
     :stepout
    
    13 15
     
    

  • testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
    ... ... @@ -8,16 +8,22 @@ x :: Int = 450
    8 8
     21    pure (x + 3)
    
    9 9
                       ^^
    
    10 10
     22  {-# OPAQUE t #-}
    
    11
    -Stopped in T8., T26042f.hs:14:3-14
    
    11
    +Stopped in T8.g, T26042f.hs:14:3-14
    
    12
    +_result :: Identity Int = _
    
    13
    +x :: Int = 225
    
    14
    +x :: Int = 225
    
    12 15
     _result :: Identity Int = _
    
    13 16
     13  g x = do
    
    14 17
     14    a <- t (x*2)
    
    15 18
           ^^^^^^^^^^^^
    
    16 19
     15    n <- pure (a+a)
    
    17
    -Stopped in T8., T26042f.hs:8:3-14
    
    20
    +Stopped in T8.f, T26042f.hs:8:3-14
    
    18 21
     _result :: Identity Int = _
    
    22
    +x :: Int = 15
    
    19 23
     7  f x = do
    
    20 24
     8    b <- g (x*x)
    
    21 25
          ^^^^^^^^^^^^
    
    22 26
     9    y <- pure (b+b)
    
    27
    +x :: Int = 15
    
    28
    +_result :: Identity Int = _
    
    23 29
     7248

  • testsuite/tests/ghci.debugger/scripts/T26042g.stdout
    ... ... @@ -6,7 +6,7 @@ x :: Int = 14
    6 6
     11  succ x = (-) (x - 2) (x + 1)
    
    7 7
                  ^^^^^^^^^^^^^^^^^^^
    
    8 8
     12  
    
    9
    -Stopped in T9., T26042g.hs:(6,3)-(8,21)
    
    9
    +Stopped in T9.top, T26042g.hs:(6,3)-(8,21)
    
    10 10
     _result :: Int = _
    
    11 11
     5  top = do
    
    12 12
        vv