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
3 changed files:
- compiler/GHC/Stg/EnforceEpt/Types.hs
- + testsuite/tests/rep-poly/T26107.hs
- testsuite/tests/rep-poly/all.T
Changes:
| ... | ... | @@ -39,8 +39,8 @@ type InferStgAlt = GenStgAlt 'InferTaggedBinders |
| 39 | 39 | combineAltInfo :: TagInfo -> TagInfo -> TagInfo
|
| 40 | 40 | combineAltInfo TagDunno _ = TagDunno
|
| 41 | 41 | combineAltInfo _ TagDunno = TagDunno
|
| 42 | -combineAltInfo (TagTuple {}) TagProper = panic "Combining unboxed tuple with non-tuple result"
|
|
| 43 | -combineAltInfo TagProper (TagTuple {}) = panic "Combining unboxed tuple with non-tuple result"
|
|
| 42 | +combineAltInfo (TagTuple {}) TagProper = TagDunno -- This can happen with rep-polymorphic result, see #26107
|
|
| 43 | +combineAltInfo TagProper (TagTuple {}) = TagDunno -- This can happen with rep-polymorphic result, see #26107
|
|
| 44 | 44 | combineAltInfo TagProper TagProper = TagProper
|
| 45 | 45 | combineAltInfo (TagTuple is1) (TagTuple is2) = TagTuple (zipWithEqual combineAltInfo is1 is2)
|
| 46 | 46 | combineAltInfo (TagTagged) ti = ti
|
| 1 | +{-# LANGUAGE GADTs, UnboxedTuples #-}
|
|
| 2 | +module T26107 where
|
|
| 3 | + |
|
| 4 | +import Data.Kind
|
|
| 5 | +import GHC.Exts
|
|
| 6 | + |
|
| 7 | +type T :: TYPE rep -> Type
|
|
| 8 | +data T a where
|
|
| 9 | + A :: T Bool
|
|
| 10 | + B :: T (# #)
|
|
| 11 | + |
|
| 12 | +f :: forall rep (a :: TYPE rep). T a -> a
|
|
| 13 | +f A = True
|
|
| 14 | +f B = (# #) |
| ... | ... | @@ -41,6 +41,7 @@ test('T23883a', normal, compile_fail, ['']) |
| 41 | 41 | test('T23883b', normal, compile_fail, [''])
|
| 42 | 42 | test('T23883c', normal, compile_fail, [''])
|
| 43 | 43 | test('T23903', normal, compile_fail, [''])
|
| 44 | +test('T26107', js_broken(22364), compile, ['-O'])
|
|
| 44 | 45 | |
| 45 | 46 | test('EtaExpandDataCon', normal, compile, ['-O'])
|
| 46 | 47 | test('EtaExpandStupid1', normal, compile, ['-Wno-deprecated-flags'])
|