summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2019-03-06 09:54:06 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-03-06 21:54:17 -0500
commit07f378cee37338c5f2655b3a7e46dfef3f1c5cc1 (patch)
treeb890d38dc6673e7755e4c47adea4e3de7d6d0d02
parentf624dc15d196507c011079eaad9a31acef87a24c (diff)
downloadhaskell-07f378cee37338c5f2655b3a7e46dfef3f1c5cc1.tar.gz
Add tests for Trac #16221 and #16342
-rw-r--r--testsuite/tests/polykinds/T16221.hs13
-rw-r--r--testsuite/tests/polykinds/T16221a.hs7
-rw-r--r--testsuite/tests/polykinds/T16221a.stderr6
-rw-r--r--testsuite/tests/polykinds/T16342.hs13
-rw-r--r--testsuite/tests/polykinds/all.T3
5 files changed, 42 insertions, 0 deletions
diff --git a/testsuite/tests/polykinds/T16221.hs b/testsuite/tests/polykinds/T16221.hs
new file mode 100644
index 0000000000..56a83748da
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs, TypeInType, ExistentialQuantification #-}
+
+module T16221 where
+
+-- Failed Lint
+data T3 a = forall k (b :: k). MkT3 (T3 b) !Int
+
+-- Works with GADT
+data T4 a where
+ MkT4 :: T4 b -> !Int -> T4 a
+
+-- Works with CUSK
+data T5 (a :: j) = forall k (b :: k). MkT5 (T5 b) !Int
diff --git a/testsuite/tests/polykinds/T16221a.hs b/testsuite/tests/polykinds/T16221a.hs
new file mode 100644
index 0000000000..50128aa826
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221a.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeInType, ExistentialQuantification #-}
+
+module T16221a where
+
+data SameKind :: k -> k -> *
+data T2 a = forall k (b :: k). MkT2 (SameKind a b) !Int
+
diff --git a/testsuite/tests/polykinds/T16221a.stderr b/testsuite/tests/polykinds/T16221a.stderr
new file mode 100644
index 0000000000..27edc2c8ec
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221a.stderr
@@ -0,0 +1,6 @@
+
+T16221a.hs:6:49: error:
+ • Expected kind ‘k1’, but ‘b’ has kind ‘k’
+ • In the second argument of ‘SameKind’, namely ‘b’
+ In the type ‘(SameKind a b)’
+ In the definition of data constructor ‘MkT2’
diff --git a/testsuite/tests/polykinds/T16342.hs b/testsuite/tests/polykinds/T16342.hs
new file mode 100644
index 0000000000..5eafcee9ec
--- /dev/null
+++ b/testsuite/tests/polykinds/T16342.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE MultiParamTypeClasses, TypeInType, ConstrainedClassMethods, ScopedTypeVariables #-}
+
+module T16342 where
+
+import Data.Proxy
+
+class C (a::ka) x where
+ cop :: D a x => x -> Proxy a -> Proxy a
+ cop _ x = x :: Proxy (a::ka)
+
+class D (b::kb) y where
+ dop :: C b y => y -> Proxy b -> Proxy b
+ dop _ x = x :: Proxy (b::kb)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 1cfb2aa424..927319c1a7 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -207,3 +207,6 @@ test('T14847', normal, compile, [''])
test('T15795', normal, compile, [''])
test('T15795a', normal, compile, [''])
test('KindVarOrder', normal, ghci_script, ['KindVarOrder.script'])
+test('T16221', normal, compile, [''])
+test('T16221a', normal, compile_fail, [''])
+test('T16342', normal, compile, [''])