[Git][ghc/ghc][master] Add regression test for #23143

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Jun 13 13:45:16 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
95b69cfb by Ryan Scott at 2023-06-13T09:44:55-04:00
Add regression test for #23143

!10541, the fix for #23323, also fixes #23143. Let's add a regression test to
ensure that it stays fixed.

Fixes #23143.

- - - - -


2 changed files:

- + testsuite/tests/quantified-constraints/T23143.hs
- testsuite/tests/quantified-constraints/all.T


Changes:

=====================================
testsuite/tests/quantified-constraints/T23143.hs
=====================================
@@ -0,0 +1,39 @@
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE InstanceSigs #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+
+{-# OPTIONS_GHC -Wredundant-constraints #-}
+
+module T23143 where
+
+import Data.Coerce
+
+newtype A a = MkA a
+
+class Pointed a where
+  point :: a
+
+class (forall a. Pointed a => Pointed (t a)) => T t where
+  points :: Pointed a => t a
+
+instance Pointed a => Pointed (A a) where
+  point = MkA point
+
+instance T A where
+  points = point
+
+newtype B a = MkB (A a)
+  deriving newtype (Pointed, T)
+
+newtype C a = MkC (A a)
+
+instance Pointed a => Pointed (C a) where
+  point :: C a
+  point = coerce @(A a) @(C a) (point @(A a))
+
+instance T C where
+  points :: forall a. Pointed a => C a
+  points = coerce @(A a) @(C a) (points @A)


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -41,5 +41,6 @@ test('T22216d', normal, compile, [''])
 test('T22216e', normal, compile, [''])
 test('T22223', normal, compile, [''])
 test('T19690', normal, compile_fail, [''])
+test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95b69cfb3d601eb3e6c5b1727c4cfef25ab87d68

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95b69cfb3d601eb3e6c5b1727c4cfef25ab87d68
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/20230613/0140b181/attachment-0001.html>


More information about the ghc-commits mailing list