[commit: ghc] wip/T16394: testsuite: Add testcase for #16394 (633c43e)

git at git.haskell.org git at git.haskell.org
Wed Mar 6 21:49:49 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T16394
Link       : http://ghc.haskell.org/trac/ghc/changeset/633c43e3ad8eb5725b92b4c359e45ab8133060a3/ghc

>---------------------------------------------------------------

commit 633c43e3ad8eb5725b92b4c359e45ab8133060a3
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Mar 5 20:33:51 2019 -0500

    testsuite: Add testcase for #16394


>---------------------------------------------------------------

633c43e3ad8eb5725b92b4c359e45ab8133060a3
 testsuite/tests/typecheck/should_fail/T16394.hs              | 12 ++++++++++++
 .../T5951.stderr => typecheck/should_fail/T16394.stderr}     |  5 ++---
 testsuite/tests/typecheck/should_fail/all.T                  |  1 +
 3 files changed, 15 insertions(+), 3 deletions(-)

diff --git a/testsuite/tests/typecheck/should_fail/T16394.hs b/testsuite/tests/typecheck/should_fail/T16394.hs
new file mode 100644
index 0000000..76ca7a7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T16394.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-}
+
+class C a where
+    type T (n :: a)
+
+instance C a => C b => C (a, b) where
+    type T '(n, m) = (T n, T m)
+
+-- but this worked fine:
+--
+-- instance (C a, C b) => C (a, b) where
+--   type T '(n, m) = (T n, T m)
diff --git a/testsuite/tests/rename/should_fail/T5951.stderr b/testsuite/tests/typecheck/should_fail/T16394.stderr
similarity index 57%
copy from testsuite/tests/rename/should_fail/T5951.stderr
copy to testsuite/tests/typecheck/should_fail/T16394.stderr
index b325493..fff51a6 100644
--- a/testsuite/tests/rename/should_fail/T5951.stderr
+++ b/testsuite/tests/typecheck/should_fail/T16394.stderr
@@ -1,6 +1,5 @@
-
-T5951.hs:8:8: error:
-    Illegal class instance: ‘A => B => C’
+T16394.hs:6:10: error:
+    Illegal class instance: ‘C a => C b => C (a, b)’
       Class instances must be of the form
         context => C ty_1 ... ty_n
       where ‘C’ is a class
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 1a775d3..b92d99c 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -510,3 +510,4 @@ test('T16059e', [extra_files(['T16059b.hs'])], multimod_compile_fail,
     ['T16059e', '-v0'])
 test('T16255', normal, compile_fail, [''])
 test('T16204c', normal, compile_fail, [''])
+test('T16394', normal, compile, [''])



More information about the ghc-commits mailing list