From 10a971208dcd537742fe4e15b2713eb0f3052a3a Mon Sep 17 00:00:00 2001
From: Ben Gamari <ben@smart-cactus.org>
Date: Tue, 5 Mar 2019 20:33:51 -0500
Subject: [PATCH] testsuite: Add testcase for #16394

---
 testsuite/tests/typecheck/should_fail/T16394.hs     | 12 ++++++++++++
 testsuite/tests/typecheck/should_fail/T16394.stderr |  5 +++++
 testsuite/tests/typecheck/should_fail/all.T         |  1 +
 3 files changed, 18 insertions(+)
 create mode 100644 testsuite/tests/typecheck/should_fail/T16394.hs
 create mode 100644 testsuite/tests/typecheck/should_fail/T16394.stderr

diff --git a/testsuite/tests/typecheck/should_fail/T16394.hs b/testsuite/tests/typecheck/should_fail/T16394.hs
new file mode 100644
index 000000000000..76ca7a7cf61d
--- /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/typecheck/should_fail/T16394.stderr b/testsuite/tests/typecheck/should_fail/T16394.stderr
new file mode 100644
index 000000000000..fff51a6e39ed
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T16394.stderr
@@ -0,0 +1,5 @@
+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 b3c25eabe92c..bd13b2f8cedc 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -510,4 +510,5 @@ 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_fail, [''])
 test('T16414', normal, compile_fail, [''])
-- 
GitLab