[Git][ghc/ghc][master] Add testcases for already fixed #16432
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Jun 1 14:59:04 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
00a1e50b by Krzysztof Gogolewski at 2023-06-01T10:58:44-04:00
Add testcases for already fixed #16432
They were fixed by 40c7daed0.
Fixes #16432
- - - - -
1 changed file:
- testsuite/tests/quantified-constraints/T23333.hs
Changes:
=====================================
testsuite/tests/quantified-constraints/T23333.hs
=====================================
@@ -1,8 +1,25 @@
{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE GADTs, DataKinds #-}
module T23333 where
+import Data.Kind
+import Data.Coerce
+
foo1 :: (forall y. Bool ~ y) => z -> Bool
foo1 x = not x
foo2 :: (forall y. y ~ Bool) => z -> Bool
foo2 x = not x
+
+-- Testcases from #16432
+t1 :: forall f b. (forall a. Coercible (f a) a) => b -> f b
+t1 = coerce
+
+data U :: () -> Type where
+ MkU :: Int -> U '()
+
+t2 :: forall n res. (('()~n) => (Int~res)) => U n -> res
+t2 (MkU n) = n
+
+t3 :: ((Bool~Bool) => (Char~res)) => res
+t3 = 'a'
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/00a1e50b65354f65f508408d171ec1af4045dd95
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/00a1e50b65354f65f508408d171ec1af4045dd95
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/20230601/6f10b7a3/attachment-0001.html>
More information about the ghc-commits
mailing list