Skip to content
Snippets Groups Projects
Commit 67dbcc0a authored by Krzysztof Gogolewski's avatar Krzysztof Gogolewski Committed by Marge Bot
Browse files

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
parent c7be0c68
No related branches found
No related tags found
No related merge requests found
......@@ -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)
......
{-# 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#
:load T24306
:force x
x = T 1 (MkA (##)) 2
......@@ -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'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment