[commit: ghc] ghc-8.2: testsuite: Add failing testcase for #13233 (c810c3c)
git at git.haskell.org
git at git.haskell.org
Mon Mar 27 02:59:28 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/c810c3c5e9c91ecf1a73d9013abf8e1c95f21ea1/ghc
>---------------------------------------------------------------
commit c810c3c5e9c91ecf1a73d9013abf8e1c95f21ea1
Author: Ben Gamari <ben at smart-cactus.org>
Date: Thu Mar 23 22:53:29 2017 -0400
testsuite: Add failing testcase for #13233
Thanks to Ryan Scott for the example.
(cherry picked from commit 27c9a7d095d2383a7822d317dc7acfe579a4815b)
>---------------------------------------------------------------
c810c3c5e9c91ecf1a73d9013abf8e1c95f21ea1
testsuite/tests/codeGen/should_compile/T13233.hs | 12 ++++++++++++
testsuite/tests/codeGen/should_compile/all.T | 1 +
2 files changed, 13 insertions(+)
diff --git a/testsuite/tests/codeGen/should_compile/T13233.hs b/testsuite/tests/codeGen/should_compile/T13233.hs
new file mode 100644
index 0000000..bb79856
--- /dev/null
+++ b/testsuite/tests/codeGen/should_compile/T13233.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE UnboxedTuples #-}
+module Bug where
+
+import GHC.Exts (TYPE)
+
+class Foo (a :: TYPE rep) where
+ bar :: forall (b :: TYPE rep2). (a -> a -> b) -> a -> a -> b
+
+baz :: forall (a :: TYPE rep). Foo a => a -> a -> (# a, a #)
+baz = bar (#,#)
diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T
index 6ae4e1c..a73a9d6 100644
--- a/testsuite/tests/codeGen/should_compile/all.T
+++ b/testsuite/tests/codeGen/should_compile/all.T
@@ -35,3 +35,4 @@ test('T10667', [ when((arch('powerpc64') or arch('powerpc64le')),
compile, ['-g'])
test('T12115', normal, compile, [''])
test('T12355', normal, compile, [''])
+test('T13233', expect_broken(13233), compile, [''])
More information about the ghc-commits
mailing list