[Git][ghc/ghc][master] Fix VoidRep handling in ghci debugger

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Jan 5 07:07:45 UTC 2024



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


Commits:
67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00
Fix VoidRep handling in ghci debugger

'go' inside extractSubTerms was giving a bad result given a VoidRep,
attempting to round towards the next multiple of 0.
I don't understand much about the debugger but the code should be better
than it was.

Fixes #24306

- - - - -


5 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- + testsuite/tests/ghci.debugger/scripts/T24306.hs
- + testsuite/tests/ghci.debugger/scripts/T24306.script
- + testsuite/tests/ghci.debugger/scripts/T24306.stdout
- testsuite/tests/ghci.debugger/scripts/all.T


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -888,13 +888,13 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
            (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
            return (ptr_i, arr_i, unboxedTupleTerm ty terms0 : terms1)
       | otherwise
-      = case typePrimRepArgs ty of
-          rep_ty :| [] ->  do
+      = case typePrimRep ty of
+          [rep_ty] -> do
             (ptr_i, arr_i, term0)  <- go_rep ptr_i arr_i ty rep_ty
             (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
             return (ptr_i, arr_i, term0 : terms1)
-          rep_ty :| rep_tys -> do
-           (ptr_i, arr_i, terms0) <- go_unary_types ptr_i arr_i (rep_ty:rep_tys)
+          rep_tys -> do
+           (ptr_i, arr_i, terms0) <- go_unary_types ptr_i arr_i rep_tys
            (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
            return (ptr_i, arr_i, unboxedTupleTerm ty terms0 : terms1)
 


=====================================
testsuite/tests/ghci.debugger/scripts/T24306.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE UnboxedTuples, UnliftedNewtypes, DataKinds, MagicHash #-}
+module T24306 where
+
+import GHC.Exts
+
+newtype A = MkA (# #)
+data T = T Int# A Int#
+
+x = T 1# (MkA (# #)) 2#


=====================================
testsuite/tests/ghci.debugger/scripts/T24306.script
=====================================
@@ -0,0 +1,2 @@
+:load T24306
+:force x


=====================================
testsuite/tests/ghci.debugger/scripts/T24306.stdout
=====================================
@@ -0,0 +1 @@
+x = T 1 (MkA (##)) 2


=====================================
testsuite/tests/ghci.debugger/scripts/all.T
=====================================
@@ -140,3 +140,4 @@ test('break030',
   ['break030.script'],
 )
 test('T23057', [only_ghci, extra_hc_opts('-fno-break-points')], ghci_script, ['T23057.script'])
+test('T24306', normal, ghci_script, ['T24306.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67dbcc0aea442a713d8fb54953ab684250794e8a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67dbcc0aea442a713d8fb54953ab684250794e8a
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/20240105/c1f1c160/attachment-0001.html>


More information about the ghc-commits mailing list