summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
authorSimon Peyton Jones <simon.peytonjones@gmail.com>2023-01-28 22:12:35 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2023-02-01 12:31:23 -0500
commit955a99ea28a0d06de67f0595d366450281aab0c0 (patch)
tree43ee724bf62c7e57403c8e60ab724c7758233afa /testsuite
parent9f95db54e38b21782d058043abe42fd77abfb9ad (diff)
downloadhaskell-955a99ea28a0d06de67f0595d366450281aab0c0.tar.gz
Treat existentials correctly in dubiousDataConInstArgTys
Consider (#22849) data T a where MkT :: forall k (t::k->*) (ix::k). t ix -> T @k a Then dubiousDataConInstArgTys MkT [Type, Foo] should return [Foo (ix::Type)] NOT [Foo (ix::k)] A bit of an obscure case, but it's an outright bug, and the fix is easy.
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/simplCore/should_compile/T22849.hs14
-rw-r--r--testsuite/tests/simplCore/should_compile/all.T3
2 files changed, 16 insertions, 1 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T22849.hs b/testsuite/tests/simplCore/should_compile/T22849.hs
new file mode 100644
index 0000000000..a4c5179251
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T22849.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE GADTs #-}
+
+module T22849 where
+
+data Foo a where
+ Foo :: Foo Int
+
+data Bar a = Bar a (Foo a)
+
+data Some t = forall ix. Some (t ix)
+
+instance Show (Some Bar) where
+ show (Some (Bar v t)) = case t of
+ Foo -> show v
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 927ac191f6..1a2ac5f7d0 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -453,7 +453,7 @@ test('T22375', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeab
test('T21851_2', [grep_errmsg(r'wwombat') ], multimod_compile, ['T21851_2', '-O -dno-typeable-binds -dsuppress-uniques'])
# Should not inline m, so there shouldn't be a single YES
test('T22317', [grep_errmsg(r'ANSWER = YES') ], compile, ['-O -dinline-check m -ddebug-output'])
-
+test('T22849', normal, compile, ['-O'])
test('T22634', normal, compile, ['-O -fcatch-nonexhaustive-cases'])
test('T22494', [grep_errmsg(r'case') ], compile, ['-O -ddump-simpl -dsuppress-uniques'])
test('T22491', normal, compile, ['-O2'])
@@ -472,3 +472,4 @@ test('T22611', [when(wordsize(32), skip), grep_errmsg(r'\$salterF') ], compile,
test('T22715_2', normal, multimod_compile, ['T22715_2', '-v0 -O -fspecialise-aggressively'])
test('T22802', normal, compile, ['-O'])
test('T15205', normal, compile, ['-O -ddump-simpl -dno-typeable-binds -dsuppress-uniques'])
+