[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Add test for T22793

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Mar 5 22:36:51 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
bf43ba92 by Simon Peyton Jones at 2023-03-04T01:18:23-05:00
Add test for T22793

- - - - -
c6e1f3cd by Chris Wendt at 2023-03-04T03:35:18-07:00
Fix typo in docs referring to threadLabel

- - - - -
87aee8fb by Simon Peyton Jones at 2023-03-05T17:36:46-05:00
Add regression test for #22328

- - - - -


6 changed files:

- docs/users_guide/9.6.1-notes.rst
- + testsuite/tests/patsyn/should_compile/T22328.hs
- testsuite/tests/patsyn/should_compile/all.T
- + testsuite/tests/polykinds/T22793.hs
- + testsuite/tests/polykinds/T22793.stderr
- testsuite/tests/polykinds/all.T


Changes:

=====================================
docs/users_guide/9.6.1-notes.rst
=====================================
@@ -197,7 +197,7 @@ Runtime system
 
 - GHC now provides a set of operations for introspecting on the threads of a
   program, ``GHC.Conc.listThreads``, as well as operations for querying a thread's
-  label (:base-ref:`GHC.Conc.threadLabel`) and status
+  label (:base-ref:`GHC.Conc.Sync.threadLabel`) and status
   (:base-ref:`GHC.Conc.threadStatus`).
 
 - Change default ``Ord`` implementation of ``(>=)``, ``(>)``, and ``(<)`` to use


=====================================
testsuite/tests/patsyn/should_compile/T22328.hs
=====================================
@@ -0,0 +1,16 @@
+{-# LANGUAGE TypeApplications, PatternSynonyms, GADTs, ViewPatterns #-}
+
+module T22328 where
+
+import Data.Typeable
+
+data Gadt x y where
+  ExistentialInGadt :: Typeable a => a -> Gadt x x
+
+pattern CastGadt :: Typeable a => x ~ y => a -> Gadt x y
+pattern CastGadt a <- ExistentialInGadt (cast -> Just a)
+
+test :: Gadt i o -> Bool
+test gadt = case gadt of
+  CastGadt @Bool a -> a
+  _ -> False


=====================================
testsuite/tests/patsyn/should_compile/all.T
=====================================
@@ -84,3 +84,4 @@ test('T14630', normal, compile, ['-Wname-shadowing'])
 test('T21531', [ grep_errmsg(r'INLINE') ], compile, ['-ddump-ds'])
 test('T22521', normal, compile, [''])
 test('T23038', normal, compile_fail, [''])
+test('T22328', normal, compile, [''])


=====================================
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/-/compare/1121bb3a87c4d05725b0491441113641a90a3bc7...87aee8fb461a58510e38d7897a7d78e54ab6fa64

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1121bb3a87c4d05725b0491441113641a90a3bc7...87aee8fb461a58510e38d7897a7d78e54ab6fa64
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/20230305/80308ac3/attachment-0001.html>


More information about the ghc-commits mailing list