summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--testsuite/tests/typecheck/should_compile/T17772.hs29
-rw-r--r--testsuite/tests/typecheck/should_compile/T18308.hs10
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
3 files changed, 41 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T17772.hs b/testsuite/tests/typecheck/should_compile/T17772.hs
new file mode 100644
index 0000000000..75d4cb3877
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T17772.hs
@@ -0,0 +1,29 @@
+{-# LANGUAGE TypeFamilies #-}
+module T17772 where
+
+import Data.Kind
+import Data.Proxy
+
+class C1 f where
+ type T1 (x :: f a) :: Type
+
+ sT1 :: forall a (x :: f a).
+ Proxy x -> T1 x
+
+class C2 a where
+ type T2 a (x :: b) :: Type
+
+ sT2 :: forall b (x :: b).
+ Proxy a -> Proxy x -> T2 a x
+
+class C3 a where
+ type T3 a :: b -> Type
+
+ sT3 :: forall b (x :: b).
+ Proxy a -> Proxy x -> T3 a x
+
+class C4 a where
+ type T4 a :: forall b. b -> Type
+
+ sT4 :: forall b (x :: b).
+ Proxy a -> Proxy x -> T4 a x
diff --git a/testsuite/tests/typecheck/should_compile/T18308.hs b/testsuite/tests/typecheck/should_compile/T18308.hs
new file mode 100644
index 0000000000..6d1e06958a
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T18308.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE NoCUSKs #-}
+{-# LANGUAGE TypeFamilies #-}
+module T18308 where
+
+import Data.Kind (Type)
+import Data.Proxy (Proxy)
+
+class Cls where
+ type Fam (k :: Type) (a :: k) :: Type
+ mtd :: Proxy k -> Proxy (a :: k) -> Fam k a -> Int
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 392f6fb40c..5e22d3332a 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -714,6 +714,7 @@ test('T17792', normal, compile, [''])
test('T17024', normal, compile, [''])
test('T19186', normal, compile, [''])
test('T17021a', normal, compile, [''])
+test('T17772', normal, compile, [''])
test('T18005', normal, compile, [''])
test('T18023', normal, compile, [''])
test('T18036', normal, compile, [''])
@@ -731,6 +732,7 @@ test('T17775-viewpats-d', normal, compile_fail, [''])
test('T18118', normal, multimod_compile, ['T18118', '-v0'])
test('T18412', normal, compile, [''])
test('T18470', normal, compile, [''])
+test('T18308', normal, compile, [''])
test('T18323', normal, compile, [''])
test('T18585', normal, compile, [''])
test('T18831', normal, compile, [''])