[Git][ghc/ghc][wip/T26107] Fix EPT enforcement when mixing unboxed tuples and non-tuples

Krzysztof Gogolewski pushed to branch wip/T26107 at Glasgow Haskell Compiler / GHC Commits: f97431c9 by Krzysztof Gogolewski at 2025-06-15T02:01:07+02:00 Fix EPT enforcement when mixing unboxed tuples and non-tuples The code was assuming that an alternative cannot be returning a normal datacon and an unboxed tuple at the same time. However, as seen in #26107, this can happen when using a GADT to refine the representation type. The solution is just to conservatively return TagDunno. - - - - - 3 changed files: - compiler/GHC/Stg/EnforceEpt/Types.hs - + testsuite/tests/rep-poly/T26107.hs - testsuite/tests/rep-poly/all.T Changes: ===================================== compiler/GHC/Stg/EnforceEpt/Types.hs ===================================== @@ -39,8 +39,8 @@ type InferStgAlt = GenStgAlt 'InferTaggedBinders combineAltInfo :: TagInfo -> TagInfo -> TagInfo combineAltInfo TagDunno _ = TagDunno combineAltInfo _ TagDunno = TagDunno -combineAltInfo (TagTuple {}) TagProper = panic "Combining unboxed tuple with non-tuple result" -combineAltInfo TagProper (TagTuple {}) = panic "Combining unboxed tuple with non-tuple result" +combineAltInfo (TagTuple {}) TagProper = TagDunno -- This can happen with rep-polymorphic result, see #26107 +combineAltInfo TagProper (TagTuple {}) = TagDunno -- This can happen with rep-polymorphic result, see #26107 combineAltInfo TagProper TagProper = TagProper combineAltInfo (TagTuple is1) (TagTuple is2) = TagTuple (zipWithEqual combineAltInfo is1 is2) combineAltInfo (TagTagged) ti = ti ===================================== testsuite/tests/rep-poly/T26107.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE GADTs, UnboxedTuples #-} +module T26107 where + +import Data.Kind +import GHC.Exts + +type T :: TYPE rep -> Type +data T a where + A :: T Bool + B :: T (# #) + +f :: forall rep (a :: TYPE rep). T a -> a +f A = True +f B = (# #) ===================================== testsuite/tests/rep-poly/all.T ===================================== @@ -41,6 +41,7 @@ test('T23883a', normal, compile_fail, ['']) test('T23883b', normal, compile_fail, ['']) test('T23883c', normal, compile_fail, ['']) test('T23903', normal, compile_fail, ['']) +test('T26107', js_broken(22364), compile, ['-O']) test('EtaExpandDataCon', normal, compile, ['-O']) test('EtaExpandStupid1', normal, compile, ['-Wno-deprecated-flags']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f97431c9b0ea6edb2c62a23aa4d04474... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f97431c9b0ea6edb2c62a23aa4d04474... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Krzysztof Gogolewski (@monoidal)