Rodrigo Mesquita pushed to branch wip/romes/step-out-11 at Glasgow Haskell Compiler / GHC
Commits:
-
cc885a91
by Rodrigo Mesquita at 2025-08-01T16:39:00+01:00
3 changed files:
Changes:
... | ... | @@ -167,7 +167,7 @@ data CgBreakInfo |
167 | 167 | { cgb_tyvars :: ![IfaceTvBndr] -- ^ Type variables in scope at the breakpoint
|
168 | 168 | , cgb_vars :: ![Maybe (IfaceIdBndr, Word)]
|
169 | 169 | , cgb_resty :: !IfaceType
|
170 | - , cgb_tick_id :: !(Either InternalBreakLoc BreakpointId)
|
|
170 | + , cgb_tick_id :: !BreakpointId
|
|
171 | 171 | -- ^ This field records the original breakpoint tick identifier for this
|
172 | 172 | -- internal breakpoint info. It is used to convert a breakpoint
|
173 | 173 | -- *occurrence* index ('InternalBreakpointId') into a *definition* index
|
... | ... | @@ -177,8 +177,10 @@ 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 | |
... | ... | @@ -207,7 +209,7 @@ 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
|
... | ... | @@ -219,24 +221,23 @@ 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 | 223 | in case cgb_tick_id cgb of
|
222 | - Left InternalBreakLoc{} -> imodBreaks_module imbs
|
|
223 | - Right BreakpointId{bi_tick_mod} -> bi_tick_mod
|
|
224 | + BreakpointId{bi_tick_mod} -> bi_tick_mod
|
|
224 | 225 | |
225 | 226 | -- | Get the source span for this breakpoint
|
226 | 227 | getBreakLoc :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO SrcSpan
|
227 | -getBreakLoc = getBreakXXX modBreaks_locs (\(InternalBreakLoc x) -> x)
|
|
228 | +getBreakLoc = getBreakXXX modBreaks_locs
|
|
228 | 229 | |
229 | 230 | -- | Get the vars for this breakpoint
|
230 | 231 | getBreakVars :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [OccName]
|
231 | -getBreakVars = getBreakXXX modBreaks_vars (const [])
|
|
232 | +getBreakVars = getBreakXXX modBreaks_vars
|
|
232 | 233 | |
233 | 234 | -- | Get the decls for this breakpoint
|
234 | 235 | getBreakDecls :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [String]
|
235 | -getBreakDecls = getBreakXXX modBreaks_decls (const [])
|
|
236 | +getBreakDecls = getBreakXXX modBreaks_decls
|
|
236 | 237 | |
237 | 238 | -- | 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)
|
|
239 | +getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO ((String, String))
|
|
240 | +getBreakCCS = getBreakXXX modBreaks_ccs
|
|
240 | 241 | |
241 | 242 | -- | Internal utility to access a ModBreaks field at a particular breakpoint index
|
242 | 243 | --
|
... | ... | @@ -253,12 +254,12 @@ getBreakCCS = getBreakXXX (fmap Just . modBreaks_ccs) (const Nothing) |
253 | 254 | --
|
254 | 255 | -- To avoid cyclic dependencies, we instead receive a function that looks up
|
255 | 256 | -- 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 =
|
|
257 | +getBreakXXX :: (ModBreaks -> Array BreakTickIndex a) -> (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO a
|
|
258 | +getBreakXXX view lookupModule (InternalBreakpointId ibi_mod ibi_ix) imbs =
|
|
258 | 259 | assert_modules_match ibi_mod (imodBreaks_module imbs) $ do
|
259 | 260 | let cgb = imodBreaks_breakInfo imbs IM.! ibi_ix
|
260 | 261 | case cgb_tick_id cgb of
|
261 | - Right BreakpointId{bi_tick_mod, bi_tick_index}
|
|
262 | + BreakpointId{bi_tick_mod, bi_tick_index}
|
|
262 | 263 | | bi_tick_mod == ibi_mod
|
263 | 264 | -> do
|
264 | 265 | let these_mbs = imodBreaks_modBreaks imbs
|
... | ... | @@ -267,8 +268,6 @@ getBreakXXX view viewInternal lookupModule (InternalBreakpointId ibi_mod ibi_ix) |
267 | 268 | -> do
|
268 | 269 | other_mbs <- lookupModule bi_tick_mod
|
269 | 270 | return $ view other_mbs ! bi_tick_index
|
270 | - Left l ->
|
|
271 | - return $ viewInternal l
|
|
272 | 271 | |
273 | 272 | --------------------------------------------------------------------------------
|
274 | 273 | -- Instances
|
... | ... | @@ -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 (cgb_tick_id info) ccss)
|
|
1719 | 1717 | )
|
1720 | 1718 | imodBreaks_breakInfo
|
1721 | 1719 | assertPpr (count == length ccs)
|
... | ... | @@ -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,6 @@ 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 ((!))
|
|
103 | 102 | |
104 | 103 | -- -----------------------------------------------------------------------------
|
105 | 104 | -- Generating byte code for a complete module
|
... | ... | @@ -406,7 +405,7 @@ schemeER_wrk d p (StgTick bp@(Breakpoint tick_ty tick_id fvs) rhs) = do |
406 | 405 | ty_vars = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
|
407 | 406 | toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
|
408 | 407 | toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
|
409 | - breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Right tick_id)
|
|
408 | + breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty tick_id
|
|
410 | 409 | |
411 | 410 | mibi <- newBreakInfo breakInfo
|
412 | 411 | |
... | ... | @@ -1341,14 +1340,13 @@ doCase d s p scrut bndr alts |
1341 | 1340 | -- continuation BCO, for step-out.
|
1342 | 1341 | -- See Note [Debugger: Stepout internal break locs]
|
1343 | 1342 | -> do
|
1344 | - internal_tick_loc <- makeCaseInternalBreakLoc tick_id
|
|
1345 | 1343 | |
1346 | 1344 | -- same fvs available in the case expression are available in the case continuation
|
1347 | 1345 | let idOffSets = getVarOffSets platform d p fvs
|
1348 | 1346 | ty_vars = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
|
1349 | 1347 | toWord :: Maybe (Id, WordOff) -> Maybe (Id, Word)
|
1350 | 1348 | toWord = fmap (\(i, wo) -> (i, fromIntegral wo))
|
1351 | - breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty (Left internal_tick_loc)
|
|
1349 | + breakInfo = dehydrateCgBreakInfo ty_vars (map toWord idOffSets) tick_ty tick_id
|
|
1352 | 1350 | |
1353 | 1351 | mibi <- newBreakInfo breakInfo
|
1354 | 1352 | return $ case mibi of
|
... | ... | @@ -1374,25 +1372,6 @@ doCase d s p scrut bndr alts |
1374 | 1372 | _ -> panic "schemeE(StgCase).push_alts"
|
1375 | 1373 | in return (PUSH_ALTS alt_bco scrut_rep `consOL` scrut_code)
|
1376 | 1374 | |
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 | 1375 | {-
|
1397 | 1376 | Note [Debugger: Stepout internal break locs]
|
1398 | 1377 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... | ... | @@ -1438,6 +1417,8 @@ always have a relevant breakpoint location: |
1438 | 1417 | - So the source location will point to the thing you've just stepped
|
1439 | 1418 | out of
|
1440 | 1419 | |
1420 | + - The variables available are the same as the ones bound just before entering
|
|
1421 | + |
|
1441 | 1422 | - Doing :step-local from there will put you on the selected
|
1442 | 1423 | alternative (which at the source level may also be the e.g. next
|
1443 | 1424 | line in a do-block)
|
... | ... | @@ -2758,9 +2739,6 @@ newBreakInfo info = BcM $ \env st -> do |
2758 | 2739 | getCurrentModule :: BcM Module
|
2759 | 2740 | getCurrentModule = BcM $ \env st -> return (bcm_module env, st)
|
2760 | 2741 | |
2761 | -getCurrentModBreaks :: BcM (Maybe ModBreaks)
|
|
2762 | -getCurrentModBreaks = BcM $ \env st -> return (modBreaks env, st)
|
|
2763 | - |
|
2764 | 2742 | withBreakTick :: StgTickish -> BcM a -> BcM a
|
2765 | 2743 | withBreakTick bp (BcM act) = BcM $ \env st ->
|
2766 | 2744 | act env{last_bp_tick=Just bp} st
|
... | ... | @@ -2774,7 +2752,7 @@ tickFS = fsLit "ticked" |
2774 | 2752 | |
2775 | 2753 | -- Dehydrating CgBreakInfo
|
2776 | 2754 | |
2777 | -dehydrateCgBreakInfo :: [TyVar] -> [Maybe (Id, Word)] -> Type -> Either InternalBreakLoc BreakpointId -> CgBreakInfo
|
|
2755 | +dehydrateCgBreakInfo :: [TyVar] -> [Maybe (Id, Word)] -> Type -> BreakpointId -> CgBreakInfo
|
|
2778 | 2756 | dehydrateCgBreakInfo ty_vars idOffSets tick_ty bid =
|
2779 | 2757 | CgBreakInfo
|
2780 | 2758 | { cgb_tyvars = map toIfaceTvBndr ty_vars
|