summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/polykinds/T11480a.hs26
-rw-r--r--testsuite/tests/polykinds/all.T1
-rw-r--r--testsuite/tests/typecheck/should_compile/T11480.hs9
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T1
4 files changed, 37 insertions, 0 deletions
diff --git a/testsuite/tests/polykinds/T11480a.hs b/testsuite/tests/polykinds/T11480a.hs
new file mode 100644
index 0000000000..3d17168082
--- /dev/null
+++ b/testsuite/tests/polykinds/T11480a.hs
@@ -0,0 +1,26 @@
+{-# language KindSignatures, PolyKinds, TypeFamilies,
+ NoImplicitPrelude, FlexibleContexts,
+ MultiParamTypeClasses, GADTs,
+ ConstraintKinds, FlexibleInstances,
+ FunctionalDependencies, UndecidableSuperClasses #-}
+
+module T11480a where
+
+import GHC.Types (Constraint)
+import qualified Prelude
+
+data Nat (c :: i -> i -> *) (d :: j -> j -> *) (f :: i -> j) (g :: i -> j)
+
+class Functor p (Nat p (->)) p => Category (p :: i -> i -> *)
+
+class (Category dom, Category cod)
+ => Functor (dom :: i -> i -> *) (cod :: j -> j -> *) (f :: i -> j)
+ | f -> dom cod
+
+instance (Category c, Category d) => Category (Nat c d)
+instance (Category c, Category d) => Functor (Nat c d) (Nat (Nat c d) (->)) (Nat c d)
+instance (Category c, Category d) => Functor (Nat c d) (->) (Nat c d f)
+
+instance Category (->)
+instance Functor (->) (->) ((->) e)
+instance Functor (->) (Nat (->) (->)) (->)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index f1f25cecc4..69c5ba0790 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -134,3 +134,4 @@ test('T11278', normal, compile, [''])
test('T11255', normal, compile, [''])
test('T11459', normal, compile_fail, [''])
test('T11466', normal, compile_fail, [''])
+test('T11480a', normal, compile, [''])
diff --git a/testsuite/tests/typecheck/should_compile/T11480.hs b/testsuite/tests/typecheck/should_compile/T11480.hs
new file mode 100644
index 0000000000..c6aafd6687
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11480.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE FlexibleContexts, UndecidableSuperClasses #-}
+
+module T11480 where
+
+class C [a] => D a
+class D a => C a
+
+foo :: C a => a -> a
+foo = undefined
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index eb4f1fb1b9..5975ed0fe9 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -497,3 +497,4 @@ test('T11462',
['', [('T11462_Plugin.hs', '-package ghc'),
('T11462.hs', '')],
'-dynamic'])
+test('T11480', normal, compile, [''])