[Git][ghc/ghc][master] 2 commits: GHCi: Lookup breakpoint CCs in the correct module

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Feb 6 15:14:06 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00
GHCi: Lookup breakpoint CCs in the correct module

We need to look up breakpoint CCs in the module that the breakpoint
points to, and not the current module.

Fixes #24327

- - - - -
b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00
testsuite: Add test for #24327

- - - - -


5 changed files:

- compiler/GHC/StgToByteCode.hs
- + testsuite/tests/ghci/T24327/T24327.hs
- + testsuite/tests/ghci/T24327/T24327.script
- + testsuite/tests/ghci/T24327/T24327A.hs
- + testsuite/tests/ghci/T24327/all.T


Changes:

=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -86,7 +86,6 @@ import qualified Data.Map as Map
 import qualified Data.IntMap as IntMap
 import qualified GHC.Data.FiniteMap as Map
 import Data.Ord
-import GHC.Stack.CCS
 import Data.Either ( partitionEithers )
 
 import GHC.Stg.Syntax
@@ -391,8 +390,7 @@ schemeER_wrk d p (StgTick (Breakpoint tick_ty tick_no fvs mod) rhs) = do
   current_mod_breaks <- getCurrentModBreaks
   case break_info hsc_env mod current_mod current_mod_breaks of
     Nothing -> pure code
-    Just ModBreaks {modBreaks_flags = breaks, modBreaks_module = mod_ptr} -> do
-      cc_arr <- getCCArray
+    Just ModBreaks {modBreaks_flags = breaks, modBreaks_module = mod_ptr, modBreaks_ccs = cc_arr} -> do
       platform <- profilePlatform <$> getProfile
       let idOffSets = getVarOffSets platform d p fvs
           ty_vars   = tyCoVarsOfTypesWellScoped (tick_ty:map idType fvs)
@@ -2260,12 +2258,6 @@ getLabelsBc n
   = BcM $ \st -> let ctr = nextlabel st
                  in return (st{nextlabel = ctr+n}, coerce [ctr .. ctr+n-1])
 
-getCCArray :: BcM (Array BreakIndex (RemotePtr CostCentre))
-getCCArray = BcM $ \st ->
-  let breaks = expectJust "GHC.StgToByteCode.getCCArray" $ modBreaks st in
-  return (st, modBreaks_ccs breaks)
-
-
 newBreakInfo :: BreakIndex -> CgBreakInfo -> BcM ()
 newBreakInfo ix info = BcM $ \st ->
   return (st{breakInfo = IntMap.insert ix info (breakInfo st)}, ())


=====================================
testsuite/tests/ghci/T24327/T24327.hs
=====================================
@@ -0,0 +1,6 @@
+module T24327 where
+import T24327A
+
+bar :: Int
+bar = foo1 'a' 1
+


=====================================
testsuite/tests/ghci/T24327/T24327.script
=====================================
@@ -0,0 +1 @@
+:l T24327


=====================================
testsuite/tests/ghci/T24327/T24327A.hs
=====================================
@@ -0,0 +1,10 @@
+module T24327A where
+
+{-# INLINE foo1 #-}
+foo1 :: Char -> Int -> Int
+foo1 _  y = bar1 y
+
+{-# INLINE bar1 #-}
+bar1 :: Int -> Int
+bar1 x = length [1..10] + x
+


=====================================
testsuite/tests/ghci/T24327/all.T
=====================================
@@ -0,0 +1 @@
+test('T24327', [extra_ways(['ghci-ext-prof']), only_ways(['ghci-ext-prof']), extra_files(['T24327A.hs', 'T24327.hs']), extra_hc_opts('-fno-unoptimized-core-for-interpreter -O')], ghci_script, ['T24327.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/532993c8160d960f848e7abd401774b6879e3ee8...b09e69587d58b129bb6eee9bb42633eb0706e6e6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/532993c8160d960f848e7abd401774b6879e3ee8...b09e69587d58b129bb6eee9bb42633eb0706e6e6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240206/5f6fc184/attachment-0001.html>


More information about the ghc-commits mailing list