summaryrefslogtreecommitdiff
path: root/testsuite/tests/polykinds
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2016-02-10 14:32:22 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2016-02-10 14:34:18 +0000
commitb565830dda0994d5d67617039db3310f81e831c8 (patch)
treece6df20d3b447d94f89e8471bf4c1fafcc40d227 /testsuite/tests/polykinds
parenta8249726585a04b46400c9b074a85097c6488bb1 (diff)
downloadhaskell-b565830dda0994d5d67617039db3310f81e831c8.tar.gz
Wrap solveEqualities in checkNoErrs
This simple change fixes Trac #11563, #11520, #11516, #11399. See esp the comments in #11520. See Note [Fail fast on kind errors] in TcSimplify Merge to 8.0 branch
Diffstat (limited to 'testsuite/tests/polykinds')
-rw-r--r--testsuite/tests/polykinds/T11399.hs7
-rw-r--r--testsuite/tests/polykinds/T11399.stderr9
-rw-r--r--testsuite/tests/polykinds/T11516.hs11
-rw-r--r--testsuite/tests/polykinds/T11516.stderr5
-rw-r--r--testsuite/tests/polykinds/T11520.hs16
-rw-r--r--testsuite/tests/polykinds/T11520.stderr6
-rw-r--r--testsuite/tests/polykinds/all.T3
7 files changed, 57 insertions, 0 deletions
diff --git a/testsuite/tests/polykinds/T11399.hs b/testsuite/tests/polykinds/T11399.hs
new file mode 100644
index 0000000000..56f1faa682
--- /dev/null
+++ b/testsuite/tests/polykinds/T11399.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE FlexibleInstances, TypeInType #-}
+module T11399 where
+
+import Data.Kind
+
+newtype UhOh (k :: * -> *) (a :: k *) = UhOh (k *)
+instance Functor k => Functor (UhOh k) where
diff --git a/testsuite/tests/polykinds/T11399.stderr b/testsuite/tests/polykinds/T11399.stderr
new file mode 100644
index 0000000000..31ccdf80b5
--- /dev/null
+++ b/testsuite/tests/polykinds/T11399.stderr
@@ -0,0 +1,9 @@
+
+T11399.hs:7:32: error:
+ • Couldn't match kind ‘*’ with ‘GHC.Types.Levity’
+ When matching kinds
+ k :: * -> *
+ TYPE :: GHC.Types.Levity -> *
+ Expected kind ‘* -> *’, but ‘UhOh k’ has kind ‘k * -> *’
+ • In the first argument of ‘Functor’, namely ‘UhOh k’
+ In the instance declaration for ‘Functor (UhOh k)’
diff --git a/testsuite/tests/polykinds/T11516.hs b/testsuite/tests/polykinds/T11516.hs
new file mode 100644
index 0000000000..3b19a997f9
--- /dev/null
+++ b/testsuite/tests/polykinds/T11516.hs
@@ -0,0 +1,11 @@
+{-# language PolyKinds #-}
+{-# language FlexibleContexts #-}
+{-# language ConstraintKinds #-}
+{-# language FlexibleInstances #-}
+{-# language FunctionalDependencies #-}
+
+import GHC.Exts (Constraint)
+
+class Ríki (p :: i -> i -> *)
+class (Ríki p) => Varpi p q f | f -> p q
+instance Varpi () () f => Varpi (->) (->) (Either f) where
diff --git a/testsuite/tests/polykinds/T11516.stderr b/testsuite/tests/polykinds/T11516.stderr
new file mode 100644
index 0000000000..5db11c8f83
--- /dev/null
+++ b/testsuite/tests/polykinds/T11516.stderr
@@ -0,0 +1,5 @@
+
+T11516.hs:11:16: error:
+ • Expected kind ‘i0 -> i0 -> *’, but ‘()’ has kind ‘*’
+ • In the first argument of ‘Varpi’, namely ‘()’
+ In the instance declaration for ‘Varpi (->) (->) (Either f)’
diff --git a/testsuite/tests/polykinds/T11520.hs b/testsuite/tests/polykinds/T11520.hs
new file mode 100644
index 0000000000..fa5a3bf4a4
--- /dev/null
+++ b/testsuite/tests/polykinds/T11520.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE RankNTypes, PolyKinds, TypeInType, GADTs, UndecidableSuperClasses #-}
+
+module T11520 where
+
+import GHC.Types hiding (TyCon)
+
+data TypeRep (a :: k)
+
+class Typeable k => Typeable (a :: k) where
+ typeRep :: TypeRep a
+
+data Compose (f :: k1 -> *) (g :: k2 -> k1) (a :: k2) = Compose (f (g a))
+
+-- Note how the kind signature on g is incorrect
+instance (Typeable f, Typeable (g :: k), Typeable k) => Typeable (Compose f g) where
+ typeRep = undefined
diff --git a/testsuite/tests/polykinds/T11520.stderr b/testsuite/tests/polykinds/T11520.stderr
new file mode 100644
index 0000000000..f598d85551
--- /dev/null
+++ b/testsuite/tests/polykinds/T11520.stderr
@@ -0,0 +1,6 @@
+
+T11520.hs:15:77: error:
+ • Expected kind ‘k20 -> k10’, but ‘g’ has kind ‘k’
+ • In the second argument of ‘Compose’, namely ‘g’
+ In the first argument of ‘Typeable’, namely ‘Compose f g’
+ In the instance declaration for ‘Typeable (Compose f g)’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 9fc15d509e..818769106f 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -137,3 +137,6 @@ test('T11466', normal, compile_fail, [''])
test('T11480a', normal, compile, [''])
test('T11480b', normal, compile, [''])
test('T11523', normal, compile, [''])
+test('T11520', normal, compile_fail, [''])
+test('T11516', normal, compile_fail, [''])
+test('T11399', normal, compile_fail, [''])