[Git][ghc/ghc][wip/t22707] Add test for T22793

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Fri Mar 3 11:19:59 UTC 2023



Simon Peyton Jones pushed to branch wip/t22707 at Glasgow Haskell Compiler / GHC


Commits:
6ba4a2dd by Simon Peyton Jones at 2023-03-03T11:20:51+00:00
Add test for T22793

- - - - -


3 changed files:

- + testsuite/tests/polykinds/T22793.hs
- + testsuite/tests/polykinds/T22793.stderr
- testsuite/tests/polykinds/all.T


Changes:

=====================================
testsuite/tests/polykinds/T22793.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+
+module T22793 where
+
+import Data.Kind
+
+type Foo :: forall k. k -> k -> Constraint
+
+class Foo s a
+
+bob :: forall {k1} {ks} {ka} q (p :: k1 -> q -> Type)
+              (f :: ka -> q) (s :: ks) (t :: ks)
+              (a :: ka) (b :: ka). Foo s a
+     => p a (f b) -> p s (f t)
+bob f = undefined


=====================================
testsuite/tests/polykinds/T22793.stderr
=====================================
@@ -0,0 +1,44 @@
+
+T22793.hs:15:42: error: [GHC-25897]
+    • Couldn't match kind ‘ka’ with ‘k1’
+      Expected kind ‘ks’, but ‘a’ has kind ‘ka’
+      ‘ka’ is a rigid type variable bound by
+        the type signature for ‘bob’
+        at T22793.hs:13:26-27
+      ‘k1’ is a rigid type variable bound by
+        the type signature for ‘bob’
+        at T22793.hs:13:16-17
+    • In the second argument of ‘Foo’, namely ‘a’
+      In the type signature:
+        bob :: forall {k1}
+                      {ks}
+                      {ka}
+                      q
+                      (p :: k1 -> q -> Type)
+                      (f :: ka -> q)
+                      (s :: ks)
+                      (t :: ks)
+                      (a :: ka)
+                      (b :: ka). Foo s a => p a (f b) -> p s (f t)
+
+T22793.hs:16:11: error: [GHC-25897]
+    • Couldn't match kind ‘ks’ with ‘k1’
+      Expected kind ‘k1’, but ‘a’ has kind ‘ka’
+      ‘ks’ is a rigid type variable bound by
+        the type signature for ‘bob’
+        at T22793.hs:13:21-22
+      ‘k1’ is a rigid type variable bound by
+        the type signature for ‘bob’
+        at T22793.hs:13:16-17
+    • In the first argument of ‘p’, namely ‘a’
+      In the type signature:
+        bob :: forall {k1}
+                      {ks}
+                      {ka}
+                      q
+                      (p :: k1 -> q -> Type)
+                      (f :: ka -> q)
+                      (s :: ks)
+                      (t :: ks)
+                      (a :: ka)
+                      (b :: ka). Foo s a => p a (f b) -> p s (f t)


=====================================
testsuite/tests/polykinds/all.T
=====================================
@@ -243,3 +243,4 @@ test('T22379a', normal, compile, [''])
 test('T22379b', normal, compile, [''])
 test('T22743', normal, compile_fail, [''])
 test('T22742', normal, compile_fail, [''])
+test('T22793', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ba4a2dda4abf17d36b55cd7625bbfa160a5b1f9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ba4a2dda4abf17d36b55cd7625bbfa160a5b1f9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230303/24e424c5/attachment-0001.html>


More information about the ghc-commits mailing list