summaryrefslogtreecommitdiff
path: root/testsuite/tests/polykinds
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/polykinds')
-rw-r--r--testsuite/tests/polykinds/PolyInstances.hs22
-rw-r--r--testsuite/tests/polykinds/PolyKinds02.stderr11
-rw-r--r--testsuite/tests/polykinds/PolyKinds04.stderr5
-rw-r--r--testsuite/tests/polykinds/PolyKinds07.stderr2
-rw-r--r--testsuite/tests/polykinds/SigTvKinds.hs7
-rw-r--r--testsuite/tests/polykinds/SigTvKinds2.hs7
-rw-r--r--testsuite/tests/polykinds/SigTvKinds2.stderr6
-rw-r--r--testsuite/tests/polykinds/T10503.stderr33
-rw-r--r--testsuite/tests/polykinds/T11142.hs10
-rw-r--r--testsuite/tests/polykinds/T11142.stderr7
-rw-r--r--testsuite/tests/polykinds/T5716.hs2
-rw-r--r--testsuite/tests/polykinds/T5716.stderr9
-rw-r--r--testsuite/tests/polykinds/T6021.hs2
-rw-r--r--testsuite/tests/polykinds/T6021.stderr9
-rw-r--r--testsuite/tests/polykinds/T6039.stderr4
-rw-r--r--testsuite/tests/polykinds/T6129.stderr2
-rw-r--r--testsuite/tests/polykinds/T7224.stderr13
-rw-r--r--testsuite/tests/polykinds/T7230.stderr6
-rw-r--r--testsuite/tests/polykinds/T7278.hs3
-rw-r--r--testsuite/tests/polykinds/T7278.stderr11
-rw-r--r--testsuite/tests/polykinds/T7328.hs2
-rw-r--r--testsuite/tests/polykinds/T7328.stderr15
-rw-r--r--testsuite/tests/polykinds/T7341.hs2
-rw-r--r--testsuite/tests/polykinds/T7341.stderr4
-rw-r--r--testsuite/tests/polykinds/T7404.stderr7
-rw-r--r--testsuite/tests/polykinds/T7438.stderr35
-rw-r--r--testsuite/tests/polykinds/T7481.stderr4
-rw-r--r--testsuite/tests/polykinds/T7524.stderr12
-rw-r--r--testsuite/tests/polykinds/T7594.hs4
-rw-r--r--testsuite/tests/polykinds/T7805.stderr8
-rw-r--r--testsuite/tests/polykinds/T7939a.stderr5
-rw-r--r--testsuite/tests/polykinds/T8566.stderr37
-rw-r--r--testsuite/tests/polykinds/T8616.stderr14
-rw-r--r--testsuite/tests/polykinds/T9200b.stderr7
-rw-r--r--testsuite/tests/polykinds/T9222.stderr32
-rw-r--r--testsuite/tests/polykinds/T9569.hs4
-rw-r--r--testsuite/tests/polykinds/all.T10
37 files changed, 217 insertions, 156 deletions
diff --git a/testsuite/tests/polykinds/PolyInstances.hs b/testsuite/tests/polykinds/PolyInstances.hs
new file mode 100644
index 0000000000..cc15126142
--- /dev/null
+++ b/testsuite/tests/polykinds/PolyInstances.hs
@@ -0,0 +1,22 @@
+{-# LANGUAGE PolyKinds, FlexibleInstances, ScopedTypeVariables,
+ UndecidableInstances #-}
+{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
+
+module PolyInstances where
+
+import GHC.Exts
+import Data.Proxy
+
+class C (a :: k)
+
+instance (C a, C b) => C (a b)
+
+data Dict :: Constraint -> *
+
+instance C Dict
+
+foo :: C p => proxy p -> ()
+foo = undefined
+
+bar :: forall (p :: Constraint) proxy. C p => proxy p -> ()
+bar _ = foo (Proxy :: Proxy (Dict p))
diff --git a/testsuite/tests/polykinds/PolyKinds02.stderr b/testsuite/tests/polykinds/PolyKinds02.stderr
index 7c5716a65e..b95cd4f207 100644
--- a/testsuite/tests/polykinds/PolyKinds02.stderr
+++ b/testsuite/tests/polykinds/PolyKinds02.stderr
@@ -1,5 +1,6 @@
-
-PolyKinds02.hs:13:16: error:
- The second argument of ‘Vec’ should have kind ‘Nat’,
- but ‘Nat’ has kind ‘*’
- In the type signature: vec :: Vec Nat Nat
+
+PolyKinds02.hs:13:16: error:
+ • Expected kind ‘Nat’, but ‘Nat’ has kind ‘*’
+ • In the second argument of ‘Vec’, namely ‘Nat’
+ In the type signature:
+ vec :: Vec Nat Nat
diff --git a/testsuite/tests/polykinds/PolyKinds04.stderr b/testsuite/tests/polykinds/PolyKinds04.stderr
index eaa4c07909..8162dd247b 100644
--- a/testsuite/tests/polykinds/PolyKinds04.stderr
+++ b/testsuite/tests/polykinds/PolyKinds04.stderr
@@ -1,8 +1,7 @@
PolyKinds04.hs:5:16:
Expecting one more argument to ‘Maybe’
- The first argument of ‘A’ should have kind ‘*’,
- but ‘Maybe’ has kind ‘* -> *’
+ Expected a type, but ‘Maybe’ has kind ‘* -> *’
+ In the first argument of ‘A’, namely ‘Maybe’
In the type ‘A Maybe’
In the definition of data constructor ‘B1’
- In the data declaration for ‘B’
diff --git a/testsuite/tests/polykinds/PolyKinds07.stderr b/testsuite/tests/polykinds/PolyKinds07.stderr
index 6b1d6c137d..3a38a6777f 100644
--- a/testsuite/tests/polykinds/PolyKinds07.stderr
+++ b/testsuite/tests/polykinds/PolyKinds07.stderr
@@ -2,6 +2,6 @@
PolyKinds07.hs:10:11:
Data constructor ‘A1’ cannot be used here
(it is defined and used in the same recursive group)
+ In the first argument of ‘B’, namely ‘A1’
In the type ‘B A1’
In the definition of data constructor ‘B1’
- In the data declaration for ‘B’
diff --git a/testsuite/tests/polykinds/SigTvKinds.hs b/testsuite/tests/polykinds/SigTvKinds.hs
new file mode 100644
index 0000000000..782a7b3f8b
--- /dev/null
+++ b/testsuite/tests/polykinds/SigTvKinds.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE PolyKinds #-}
+
+module SigTvKinds where
+
+data T (a :: k1) x = MkT (S a ())
+data S (b :: k2) y = MkS (T b ())
+ -- tests TcTyClsDecls.no_sig_tv
diff --git a/testsuite/tests/polykinds/SigTvKinds2.hs b/testsuite/tests/polykinds/SigTvKinds2.hs
new file mode 100644
index 0000000000..1ec1ebb0f6
--- /dev/null
+++ b/testsuite/tests/polykinds/SigTvKinds2.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE PolyKinds #-}
+
+module SigTvKinds2 where
+
+data SameKind :: k -> k -> *
+
+data Q (a :: k1) (b :: k2) c = MkQ (SameKind a b)
diff --git a/testsuite/tests/polykinds/SigTvKinds2.stderr b/testsuite/tests/polykinds/SigTvKinds2.stderr
new file mode 100644
index 0000000000..9f523705a6
--- /dev/null
+++ b/testsuite/tests/polykinds/SigTvKinds2.stderr
@@ -0,0 +1,6 @@
+
+SigTvKinds2.hs:7:48: error:
+ • Expected kind ‘k1’, but ‘b’ has kind ‘k2’
+ • In the second argument of ‘SameKind’, namely ‘b’
+ In the type ‘SameKind a b’
+ In the definition of data constructor ‘MkQ’
diff --git a/testsuite/tests/polykinds/T10503.stderr b/testsuite/tests/polykinds/T10503.stderr
index 071ab5e88e..7c39c41738 100644
--- a/testsuite/tests/polykinds/T10503.stderr
+++ b/testsuite/tests/polykinds/T10503.stderr
@@ -1,15 +1,18 @@
-
-T10503.hs:8:6: error:
- Couldn't match kind ‘k’ with ‘*’
- ‘k’ is a rigid type variable bound by
- the type signature for:
- h :: forall (k :: BOX) r.
- ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r
- at T10503.hs:8:6
- Expected type: Proxy 'KProxy
- Actual type: Proxy 'KProxy
- In the ambiguity check for ‘h’
- To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
- In the type signature:
- h :: forall r.
- (Proxy (KProxy :: KProxy k) ~ Proxy (KProxy :: KProxy *) => r) -> r
+
+T10503.hs:8:6: error:
+ • Could not deduce: k ~ *
+ from the context: Proxy 'KProxy ~ Proxy 'KProxy
+ bound by the type signature for:
+ h :: (Proxy 'KProxy ~ Proxy 'KProxy) => r
+ at T10503.hs:8:6-85
+ ‘k’ is a rigid type variable bound by
+ the type signature for:
+ h :: forall k r. ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r
+ at T10503.hs:8:6
+ Expected type: ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r
+ Actual type: ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r
+ • In the ambiguity check for ‘h’
+ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+ In the type signature:
+ h :: forall r.
+ (Proxy (KProxy :: KProxy k) ~ Proxy (KProxy :: KProxy *) => r) -> r
diff --git a/testsuite/tests/polykinds/T11142.hs b/testsuite/tests/polykinds/T11142.hs
new file mode 100644
index 0000000000..58eb3b6c94
--- /dev/null
+++ b/testsuite/tests/polykinds/T11142.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TypeInType, RankNTypes #-}
+
+module T11142 where
+
+import Data.Kind
+
+data SameKind :: k -> k -> *
+
+foo :: forall b. (forall k (a :: k). SameKind a b) -> ()
+foo = undefined
diff --git a/testsuite/tests/polykinds/T11142.stderr b/testsuite/tests/polykinds/T11142.stderr
new file mode 100644
index 0000000000..2cb4e61f19
--- /dev/null
+++ b/testsuite/tests/polykinds/T11142.stderr
@@ -0,0 +1,7 @@
+
+T11142.hs:9:8: error:
+ • The kind of variable ‘b’, namely ‘k’,
+ depends on variable ‘k’ from an inner scope
+ Perhaps bind ‘b’ sometime after binding ‘k’
+ • In the type signature:
+ foo :: forall b. (forall k (a :: k). SameKind a b) -> ()
diff --git a/testsuite/tests/polykinds/T5716.hs b/testsuite/tests/polykinds/T5716.hs
index 572de5e4e8..1b705a36b1 100644
--- a/testsuite/tests/polykinds/T5716.hs
+++ b/testsuite/tests/polykinds/T5716.hs
@@ -5,7 +5,7 @@
module T5716 where
-data family DF a
+data family DF a
data instance DF Int = DFInt
data U = U1 (DF Int)
diff --git a/testsuite/tests/polykinds/T5716.stderr b/testsuite/tests/polykinds/T5716.stderr
index 227a6b88c6..8bc8883daf 100644
--- a/testsuite/tests/polykinds/T5716.stderr
+++ b/testsuite/tests/polykinds/T5716.stderr
@@ -1,4 +1,7 @@
-T5716.hs:13:11:
- ‘U’ of kind ‘*’ is not promotable
- In the kind ‘U -> *’
+T5716.hs:13:33: error:
+ Data constructor ‘U1’ cannot be used here
+ (Perhaps you intended to use TypeInType)
+ In the first argument of ‘I’, namely ‘U1 DFInt’
+ In the type ‘I (U1 DFInt)’
+ In the definition of data constructor ‘I1’
diff --git a/testsuite/tests/polykinds/T6021.hs b/testsuite/tests/polykinds/T6021.hs
index 0a89bf9570..77915a266e 100644
--- a/testsuite/tests/polykinds/T6021.hs
+++ b/testsuite/tests/polykinds/T6021.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE KindSignatures, PolyKinds, MultiParamTypeClasses #-}
+{-# LANGUAGE KindSignatures, PolyKinds, MultiParamTypeClasses, FlexibleInstances #-}
module T6021 where
class Panic a b
diff --git a/testsuite/tests/polykinds/T6021.stderr b/testsuite/tests/polykinds/T6021.stderr
index 0b7ce77439..d747043d27 100644
--- a/testsuite/tests/polykinds/T6021.stderr
+++ b/testsuite/tests/polykinds/T6021.stderr
@@ -1,5 +1,4 @@
-
-T6021.hs:5:22: error:
- Type variable ‘b’ used as a kind
- In the kind ‘b’
- In the instance declaration for ‘Panic (a :: b) b’
+
+T6021.hs:5:22: error:
+ Variable ‘b’ used as both a kind and a type
+ Did you intend to use TypeInType?
diff --git a/testsuite/tests/polykinds/T6039.stderr b/testsuite/tests/polykinds/T6039.stderr
deleted file mode 100644
index def904ea33..0000000000
--- a/testsuite/tests/polykinds/T6039.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-T6039.hs:5:14:
- Kind variable ‘j’ cannot appear in a function position
- In the kind ‘j k’
diff --git a/testsuite/tests/polykinds/T6129.stderr b/testsuite/tests/polykinds/T6129.stderr
index 36b749680b..451d851c5d 100644
--- a/testsuite/tests/polykinds/T6129.stderr
+++ b/testsuite/tests/polykinds/T6129.stderr
@@ -2,6 +2,6 @@
T6129.hs:12:11:
Data constructor ‘DInt’ cannot be used here
(it comes from a data family instance)
+ In the first argument of ‘X’, namely ‘DInt’
In the type ‘X DInt’
In the definition of data constructor ‘X1’
- In the data declaration for ‘X’
diff --git a/testsuite/tests/polykinds/T7224.stderr b/testsuite/tests/polykinds/T7224.stderr
index b957a1ba65..daab1c40a9 100644
--- a/testsuite/tests/polykinds/T7224.stderr
+++ b/testsuite/tests/polykinds/T7224.stderr
@@ -1,6 +1,7 @@
-
-T7224.hs:6:19: error:
- Kind variable ‘i’ used as a type
- In the type signature:
- ret' :: a -> m i i a
- In the class declaration for ‘PMonad'’
+
+T7224.hs:6:19: error:
+ • Expected kind ‘i’, but ‘i’ has kind ‘*’
+ • In the first argument of ‘m’, namely ‘i’
+ In the type signature:
+ ret' :: a -> m i i a
+ In the class declaration for ‘PMonad'’
diff --git a/testsuite/tests/polykinds/T7230.stderr b/testsuite/tests/polykinds/T7230.stderr
index 92938bedb1..36e333c5ec 100644
--- a/testsuite/tests/polykinds/T7230.stderr
+++ b/testsuite/tests/polykinds/T7230.stderr
@@ -8,18 +8,18 @@ T7230.hs:48:32: error:
at T7230.hs:47:1-68
or from: xs ~ (x : xs1)
bound by a pattern with constructor:
- SCons :: forall (k :: BOX) (x :: k) (xs :: [k]).
+ SCons :: forall a (x :: a) (xs :: [a]).
Sing x -> Sing xs -> Sing (x : xs),
in an equation for ‘crash’
at T7230.hs:48:8-27
or from: xs1 ~ (x1 : xs2)
bound by a pattern with constructor:
- SCons :: forall (k :: BOX) (x :: k) (xs :: [k]).
+ SCons :: forall a (x :: a) (xs :: [a]).
Sing x -> Sing xs -> Sing (x : xs),
in an equation for ‘crash’
at T7230.hs:48:17-26
Expected type: SBool (Increasing xs)
- Actual type: SBool (x :<<= x1)
+ Actual type: SBool (x :<<= x1)
• In the expression: x %:<<= y
In an equation for ‘crash’:
crash (SCons x (SCons y xs)) = x %:<<= y
diff --git a/testsuite/tests/polykinds/T7278.hs b/testsuite/tests/polykinds/T7278.hs
index d43e60c7a7..af4800507e 100644
--- a/testsuite/tests/polykinds/T7278.hs
+++ b/testsuite/tests/polykinds/T7278.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE TypeFamilies, PolyKinds, MultiParamTypeClasses #-}
+{-# LANGUAGE TypeFamilies, PolyKinds, MultiParamTypeClasses, FlexibleContexts,
+ AllowAmbiguousTypes #-}
module T7278 where
type family TF (t :: k) :: * -> * -> *
diff --git a/testsuite/tests/polykinds/T7278.stderr b/testsuite/tests/polykinds/T7278.stderr
index f8b2cfface..676be2cb0f 100644
--- a/testsuite/tests/polykinds/T7278.stderr
+++ b/testsuite/tests/polykinds/T7278.stderr
@@ -1,5 +1,6 @@
-
-T7278.hs:8:43: error:
- ‘t’ is applied to too many type arguments
- In the type signature:
- f :: (C (t :: k) (TF t)) => TF t p1 p0 -> t p1 p0
+
+T7278.hs:9:43: error:
+ • Expecting two fewer arguments to ‘t’
+ Expected kind ‘* -> * -> *’, but ‘t’ has kind ‘k’
+ • In the type signature:
+ f :: (C (t :: k) (TF t)) => TF t p1 p0 -> t p1 p0
diff --git a/testsuite/tests/polykinds/T7328.hs b/testsuite/tests/polykinds/T7328.hs
index 3e51875508..f51efb7943 100644
--- a/testsuite/tests/polykinds/T7328.hs
+++ b/testsuite/tests/polykinds/T7328.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PolyKinds, GADTs #-}
+{-# LANGUAGE PolyKinds, GADTs, AllowAmbiguousTypes #-}
module T7328 where
diff --git a/testsuite/tests/polykinds/T7328.stderr b/testsuite/tests/polykinds/T7328.stderr
index 9e7cbab03a..31b425f644 100644
--- a/testsuite/tests/polykinds/T7328.stderr
+++ b/testsuite/tests/polykinds/T7328.stderr
@@ -1,8 +1,7 @@
-
-T7328.hs:8:34: error:
- Kind occurs check
- The first argument of ‘Foo’ should have kind ‘k0’,
- but ‘f’ has kind ‘k1 -> k0’
- In the type signature:
- foo :: a ~ f i => Proxy (Foo f)
- In the class declaration for ‘Foo’
+
+T7328.hs:8:34: error:
+ • Occurs check: cannot construct the infinite kind: k10 ~ k0 -> k10
+ • In the first argument of ‘Foo’, namely ‘f’
+ In the first argument of ‘Proxy’, namely ‘Foo f’
+ In the type signature:
+ foo :: a ~ f i => Proxy (Foo f)
diff --git a/testsuite/tests/polykinds/T7341.hs b/testsuite/tests/polykinds/T7341.hs
index 1c91847dfc..79d056532a 100644
--- a/testsuite/tests/polykinds/T7341.hs
+++ b/testsuite/tests/polykinds/T7341.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE KindSignatures, TypeFamilies, PolyKinds #-}
+{-# LANGUAGE KindSignatures, TypeFamilies, PolyKinds, FlexibleInstances #-}
module T7341 where
diff --git a/testsuite/tests/polykinds/T7341.stderr b/testsuite/tests/polykinds/T7341.stderr
index c5dd260660..925c68e52d 100644
--- a/testsuite/tests/polykinds/T7341.stderr
+++ b/testsuite/tests/polykinds/T7341.stderr
@@ -1,6 +1,6 @@
T7341.hs:11:12:
Expecting one more argument to ‘[]’
- The first argument of ‘C’ should have kind ‘*’,
- but ‘[]’ has kind ‘* -> *’
+ Expected a type, but ‘[]’ has kind ‘* -> *’
+ In the first argument of ‘C’, namely ‘[]’
In the instance declaration for ‘C []’
diff --git a/testsuite/tests/polykinds/T7404.stderr b/testsuite/tests/polykinds/T7404.stderr
index d9d4288c56..a8b953e5df 100644
--- a/testsuite/tests/polykinds/T7404.stderr
+++ b/testsuite/tests/polykinds/T7404.stderr
@@ -1,4 +1,5 @@
-T7404.hs:4:1:
- Kind variable also used as type variable: ‘x’
- In the declaration for type family ‘Foo’
+T7404.hs:4:32: error:
+ Type variable ‘x’ used in a kind.
+ Did you mean to use TypeInType?
+ the declaration for type family ‘Foo’
diff --git a/testsuite/tests/polykinds/T7438.stderr b/testsuite/tests/polykinds/T7438.stderr
index ca09383a2d..539d15d406 100644
--- a/testsuite/tests/polykinds/T7438.stderr
+++ b/testsuite/tests/polykinds/T7438.stderr
@@ -1,20 +1,19 @@
T7438.hs:6:14: error:
- Couldn't match expected type ‘t1’ with actual type ‘t’
- ‘t’ is untouchable
- inside the constraints: t2 ~ t3
- bound by a pattern with constructor:
- Nil :: forall (k :: BOX) (b :: k). Thrist b b,
- in an equation for ‘go’
- at T7438.hs:6:4-6
- ‘t’ is a rigid type variable bound by
- the inferred type of go :: Thrist t2 t3 -> t -> t1 at T7438.hs:6:1
- ‘t1’ is a rigid type variable bound by
- the inferred type of go :: Thrist t2 t3 -> t -> t1 at T7438.hs:6:1
- Possible fix: add a type signature for ‘go’
- In the expression: acc
- In an equation for ‘go’: go Nil acc = acc
- Relevant bindings include
- acc :: t (bound at T7438.hs:6:8)
- go :: Thrist t2 t3 -> t -> t1 (bound at T7438.hs:6:1)
-
+ • Couldn't match expected type ‘r1’ with actual type ‘r’
+ ‘r1’ is untouchable
+ inside the constraints: r3 ~ r2
+ bound by a pattern with constructor:
+ Nil :: forall k (a :: k). Thrist a a,
+ in an equation for ‘go’
+ at T7438.hs:6:4-6
+ ‘r1’ is a rigid type variable bound by
+ the inferred type of go :: Thrist r2 r3 -> r -> r1 at T7438.hs:6:1
+ ‘r’ is a rigid type variable bound by
+ the inferred type of go :: Thrist r2 r3 -> r -> r1 at T7438.hs:6:1
+ Possible fix: add a type signature for ‘go’
+ • In the expression: acc
+ In an equation for ‘go’: go Nil acc = acc
+ • Relevant bindings include
+ acc :: r (bound at T7438.hs:6:8)
+ go :: Thrist r2 r3 -> r -> r1 (bound at T7438.hs:6:1)
diff --git a/testsuite/tests/polykinds/T7481.stderr b/testsuite/tests/polykinds/T7481.stderr
deleted file mode 100644
index cca905d5e5..0000000000
--- a/testsuite/tests/polykinds/T7481.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-T7481.hs:12:13:
- ‘D’ of kind ‘* -> *’ is not promotable
- In the kind ‘D * -> *’
diff --git a/testsuite/tests/polykinds/T7524.stderr b/testsuite/tests/polykinds/T7524.stderr
index 83b355e312..2340ce1aa6 100644
--- a/testsuite/tests/polykinds/T7524.stderr
+++ b/testsuite/tests/polykinds/T7524.stderr
@@ -1,6 +1,6 @@
-
-T7524.hs:5:15:
- Conflicting family instance declarations:
- forall (k :: BOX) (a :: k). F a a = Int -- Defined at T7524.hs:5:15
- forall (k :: BOX) (k1 :: BOX) (a :: k) (b :: k1).
- F a b = Bool -- Defined at T7524.hs:6:15
+
+T7524.hs:5:15: error:
+ Conflicting family instance declarations:
+ forall k2 (a :: k2). F a a = Int -- Defined at T7524.hs:5:15
+ forall k2 k1 (a :: k1) (b :: k2).
+ F a b = Bool -- Defined at T7524.hs:6:15
diff --git a/testsuite/tests/polykinds/T7594.hs b/testsuite/tests/polykinds/T7594.hs
index 2cbd3db88d..18da70342c 100644
--- a/testsuite/tests/polykinds/T7594.hs
+++ b/testsuite/tests/polykinds/T7594.hs
@@ -8,7 +8,7 @@
{-# LANGUAGE Rank2Types #-}
module T7594 where
-import GHC.Prim (Constraint)
+import GHC.Exts (Constraint)
class (c1 t, c2 t) => (:&:) (c1 :: * -> Constraint) (c2 :: * -> Constraint) (t :: *)
instance (c1 t, c2 t) => (:&:) c1 c2 t
@@ -33,5 +33,3 @@ q2 = error "urk"
bar2 = app print q2
-- This one fail, because the given constraint is
-- (c :&: Real) a, which might have equality superclasses
-
-
diff --git a/testsuite/tests/polykinds/T7805.stderr b/testsuite/tests/polykinds/T7805.stderr
index bdf0f21b14..33b9d4df6b 100644
--- a/testsuite/tests/polykinds/T7805.stderr
+++ b/testsuite/tests/polykinds/T7805.stderr
@@ -1,4 +1,6 @@
-T7805.hs:6:21:
- ‘HigherRank’ of kind ‘*’ is not promotable
- In the kind ‘HigherRank’
+T7805.hs:7:21: error:
+ Expected kind ‘forall a. a -> a’, but ‘x’ has kind ‘k0’
+ In the first argument of ‘HR’, namely ‘x’
+ In the first argument of ‘F’, namely ‘HR x’
+ In the type instance declaration for ‘F’
diff --git a/testsuite/tests/polykinds/T7939a.stderr b/testsuite/tests/polykinds/T7939a.stderr
index 22388ddca0..4b24b3dc72 100644
--- a/testsuite/tests/polykinds/T7939a.stderr
+++ b/testsuite/tests/polykinds/T7939a.stderr
@@ -1,7 +1,6 @@
T7939a.hs:7:5:
Expecting one more argument to ‘Maybe’
- The first argument of ‘F’ should have kind ‘*’,
- but ‘Maybe’ has kind ‘* -> *’
- In the type ‘Maybe’
+ Expected a type, but ‘Maybe’ has kind ‘* -> *’
+ In the first argument of ‘F’, namely ‘Maybe’
In the type family declaration for ‘F’
diff --git a/testsuite/tests/polykinds/T8566.stderr b/testsuite/tests/polykinds/T8566.stderr
index 168e890404..1e7818c5ef 100644
--- a/testsuite/tests/polykinds/T8566.stderr
+++ b/testsuite/tests/polykinds/T8566.stderr
@@ -1,19 +1,18 @@
-
-T8566.hs:32:9:
- Could not deduce (C ('AA (t (I a ps)) as) ps fs0)
- arising from a use of ‘c’
- from the context: C ('AA (t (I a ps)) as) ps fs
- bound by the instance declaration at T8566.hs:30:10-67
- or from: 'AA t (a : as) ~ 'AA t1 as1
- bound by a pattern with constructor:
- A :: forall (r :: [*]) (k :: BOX) (t :: k) (as :: [U *]).
- I ('AA t as) r,
- in an equation for ‘c’
- at T8566.hs:32:5
- The type variable ‘fs0’ is ambiguous
- Relevant bindings include
- c :: I ('AA t (a : as)) ps -> I ('AA t (a : as)) ps
- (bound at T8566.hs:32:3)
- In the expression: c undefined
- In an equation for ‘c’: c A = c undefined
- In the instance declaration for ‘C ('AA t (a : as)) ps fs’
+
+T8566.hs:32:9: error:
+ • Could not deduce (C ('AA (t (I a ps)) as) ps fs0)
+ arising from a use of ‘c’
+ from the context: C ('AA (t (I a ps)) as) ps fs
+ bound by the instance declaration at T8566.hs:30:10-67
+ or from: 'AA t (a : as) ~ 'AA t1 as1
+ bound by a pattern with constructor:
+ A :: forall (r :: [*]) v (t :: v) (as :: [U *]). I ('AA t as) r,
+ in an equation for ‘c’
+ at T8566.hs:32:5
+ The type variable ‘fs0’ is ambiguous
+ Relevant bindings include
+ c :: I ('AA t (a : as)) ps -> I ('AA t (a : as)) ps
+ (bound at T8566.hs:32:3)
+ • In the expression: c undefined
+ In an equation for ‘c’: c A = c undefined
+ In the instance declaration for ‘C ('AA t (a : as)) ps fs’
diff --git a/testsuite/tests/polykinds/T8616.stderr b/testsuite/tests/polykinds/T8616.stderr
index 5c8449826d..00c9c6328e 100644
--- a/testsuite/tests/polykinds/T8616.stderr
+++ b/testsuite/tests/polykinds/T8616.stderr
@@ -1,7 +1,9 @@
-T8616.hs:8:29:
- Expected a type, but ‘Any’ has kind ‘k’
- In an expression type signature: (Any :: k)
- In the expression: undefined :: (Any :: k)
- In an equation for ‘withSomeSing’:
- withSomeSing = undefined :: (Any :: k)
+T8616.hs:8:29: error:
+ • Expected a type, but ‘Any’ has kind ‘k’
+ • In an expression type signature: (Any :: k)
+ In the expression: undefined :: (Any :: k)
+ In an equation for ‘withSomeSing’:
+ withSomeSing = undefined :: (Any :: k)
+ • Relevant bindings include
+ withSomeSing :: Proxy kproxy (bound at T8616.hs:8:1)
diff --git a/testsuite/tests/polykinds/T9200b.stderr b/testsuite/tests/polykinds/T9200b.stderr
index 5e8c730878..22f9df73f1 100644
--- a/testsuite/tests/polykinds/T9200b.stderr
+++ b/testsuite/tests/polykinds/T9200b.stderr
@@ -1,6 +1,5 @@
-T9200b.hs:8:5:
- The first argument of ‘F’ should have kind ‘k’,
- but ‘True’ has kind ‘Bool’
- In the type ‘True’
+T9200b.hs:8:5: error:
+ Expected kind ‘k’, but ‘'True’ has kind ‘Bool’
+ In the first argument of ‘F’, namely ‘True’
In the type family declaration for ‘F’
diff --git a/testsuite/tests/polykinds/T9222.stderr b/testsuite/tests/polykinds/T9222.stderr
index 6a45c4a7fb..69e850caf8 100644
--- a/testsuite/tests/polykinds/T9222.stderr
+++ b/testsuite/tests/polykinds/T9222.stderr
@@ -1,19 +1,19 @@
T9222.hs:13:3: error:
- Couldn't match type ‘b0’ with ‘b’
- ‘b0’ is untouchable
- inside the constraints: a ~ '(b0, c0)
- bound by the type of the constructor ‘Want’:
- (a ~ '(b0, c0)) => Proxy b0
+ • Couldn't match type ‘b0’ with ‘b’
+ ‘b0’ is untouchable
+ inside the constraints: a ~ '(b0, c0)
+ bound by the type of the constructor ‘Want’:
+ (a ~ '(b0, c0)) => Proxy b0
+ at T9222.hs:13:3
+ ‘b’ is a rigid type variable bound by
+ the type of the constructor ‘Want’:
+ forall i j (a :: (i, j)) (b :: i) (c :: j).
+ ((a ~ '(b, c)) => Proxy b) -> Want a
at T9222.hs:13:3
- ‘b’ is a rigid type variable bound by
- the type of the constructor ‘Want’:
- forall (k :: BOX) (k1 :: BOX) (a :: (,) k k1) (b :: k) (c :: k1).
- ((a ~ '(b, c)) => Proxy b) -> Want a
- at T9222.hs:13:3
- Expected type: '(b, c)
- Actual type: a
- In the ambiguity check for ‘Want’
- To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
- In the definition of data constructor ‘Want’
- In the data type declaration for ‘Want’
+ Expected type: Proxy b0
+ Actual type: Proxy b
+ • In the ambiguity check for ‘Want’
+ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+ In the definition of data constructor ‘Want’
+ In the data type declaration for ‘Want’
diff --git a/testsuite/tests/polykinds/T9569.hs b/testsuite/tests/polykinds/T9569.hs
index 0e1fdd596a..1b8bb68c75 100644
--- a/testsuite/tests/polykinds/T9569.hs
+++ b/testsuite/tests/polykinds/T9569.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE RankNTypes, ConstraintKinds, KindSignatures, DataKinds, TypeFamilies #-}
module T9569 where
-import GHC.Prim
+import GHC.Exts
data Proxy (c :: Constraint)
@@ -23,4 +23,4 @@ instance (Deferrable c1, Deferrable c2) => Deferrable (c1,c2) where
[W] Proxy (c1,c2) -> ((c1,c2) => a) -> a ~ Proxy (c1x,c2x) -> ((c1x,c2x) => ax) -> ax
[w] Deferrable c1x
[w] Deferrable c2x
--} \ No newline at end of file
+-}
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index b1e0793a4e..a93ad8bc41 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -37,7 +37,7 @@ test('T6035', normal, compile, [''])
test('T6036', normal, compile, [''])
test('T6025', normal, run_command, ['$MAKE -s --no-print-directory T6025'])
test('T6002', normal, compile, [''])
-test('T6039', normal, compile_fail, [''])
+test('T6039', normal, compile, [''])
test('T6021', normal, compile_fail, [''])
test('T6020a', normal, compile, [''])
test('T6044', normal, compile, [''])
@@ -94,8 +94,8 @@ test('T8449', normal, run_command, ['$MAKE -s --no-print-directory T8449'])
test('T8534', normal, compile, [''])
test('T8566', normal, compile_fail,[''])
test('T8616', normal, compile_fail,[''])
-test('T8566a', expect_broken(8566), compile,[''])
-test('T7481', normal, compile_fail,[''])
+test('T8566a', normal, compile,[''])
+test('T7481', normal, compile,[''])
test('T8705', normal, compile, [''])
test('T8985', normal, compile, [''])
test('T9106', normal, compile_fail, [''])
@@ -112,6 +112,7 @@ test('T9838', normal, multimod_compile, ['T9838.hs','-v0'])
test('T9574', normal, compile_fail, [''])
test('T9833', normal, compile, [''])
test('T7908', normal, compile, [''])
+test('PolyInstances', normal, compile, [''])
test('T10041', normal, compile, [''])
test('T10451', normal, compile_fail, [''])
test('T10516', normal, compile_fail, [''])
@@ -122,3 +123,6 @@ test('T10670a', normal, compile, [''])
test('T10134', normal, multimod_compile, ['T10134.hs','-v0'])
test('T10742', normal, compile, [''])
test('T10934', normal, compile, [''])
+test('T11142', normal, compile_fail, [''])
+test('SigTvKinds', expect_broken(11203), compile, [''])
+test('SigTvKinds2', expect_broken(11203), compile_fail, [''])