summaryrefslogtreecommitdiff
path: root/testsuite/tests/quantified-constraints
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/quantified-constraints')
-rw-r--r--testsuite/tests/quantified-constraints/T15359.hs12
-rw-r--r--testsuite/tests/quantified-constraints/T15359a.hs14
-rw-r--r--testsuite/tests/quantified-constraints/T15625.hs16
-rw-r--r--testsuite/tests/quantified-constraints/T15625a.hs20
-rw-r--r--testsuite/tests/quantified-constraints/all.T4
5 files changed, 66 insertions, 0 deletions
diff --git a/testsuite/tests/quantified-constraints/T15359.hs b/testsuite/tests/quantified-constraints/T15359.hs
new file mode 100644
index 0000000000..7ef1cc5572
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15359.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE MultiParamTypeClasses, GADTs, RankNTypes,
+ ConstraintKinds, QuantifiedConstraints #-}
+
+module T15359 where
+
+class C a b
+
+data Dict c where
+ Dict :: c => Dict c
+
+foo :: (forall a b. C a b => a ~ b) => Dict (C a b) -> a -> b
+foo Dict x = x
diff --git a/testsuite/tests/quantified-constraints/T15359a.hs b/testsuite/tests/quantified-constraints/T15359a.hs
new file mode 100644
index 0000000000..6ec5f861a8
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15359a.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE MultiParamTypeClasses, GADTs, RankNTypes,
+ ConstraintKinds, QuantifiedConstraints,
+ UndecidableInstances #-}
+
+module T15359a where
+
+class C a b
+class a ~ b => D a b
+
+data Dict c where
+ Dict :: c => Dict c
+
+foo :: (forall a b. C a b => D a b) => Dict (C a b) -> a -> b
+foo Dict x = x
diff --git a/testsuite/tests/quantified-constraints/T15625.hs b/testsuite/tests/quantified-constraints/T15625.hs
new file mode 100644
index 0000000000..8fe092da98
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15625.hs
@@ -0,0 +1,16 @@
+{-# Language GADTs, MultiParamTypeClasses, QuantifiedConstraints #-}
+
+module T15625 where
+
+import Data.Coerce
+
+class a ~ b => Equal a b
+
+test1 :: (forall b. a ~ b) => a
+test1 = False
+
+test2 :: (forall b. Equal a b) => a
+test2 = False
+
+test3 :: (forall b. Coercible a b) => a
+test3 = coerce False
diff --git a/testsuite/tests/quantified-constraints/T15625a.hs b/testsuite/tests/quantified-constraints/T15625a.hs
new file mode 100644
index 0000000000..ca049cb19d
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15625a.hs
@@ -0,0 +1,20 @@
+{-# Language RankNTypes, ConstraintKinds, QuantifiedConstraints,
+ PolyKinds, GADTs, MultiParamTypeClasses,
+ DataKinds, FlexibleInstances #-}
+
+module T15625a where
+
+import Data.Kind
+
+type Cat ob = ob -> ob -> Type
+
+data KLEISLI (m :: Type -> Type) :: Cat (KL_kind m) where
+ MkKLEISLI :: (a -> m b) -> KLEISLI(m) (KL a) (KL b)
+
+data KL_kind (m :: Type -> Type) = KL Type
+
+class (a ~ KL xx) => AsKL a xx
+instance (a ~ KL xx) => AsKL a xx
+
+ekki__ :: Monad m => (forall xx. AsKL a xx) => KLEISLI m a a
+ekki__ = MkKLEISLI undefined
diff --git a/testsuite/tests/quantified-constraints/all.T b/testsuite/tests/quantified-constraints/all.T
index 833a667ea9..1e2eca8358 100644
--- a/testsuite/tests/quantified-constraints/all.T
+++ b/testsuite/tests/quantified-constraints/all.T
@@ -16,3 +16,7 @@ test('T15290a', normal, compile_fail, [''])
test('T15290b', normal, compile_fail, [''])
test('T15316', normal, compile_fail, [''])
test('T15334', normal, compile_fail, [''])
+test('T15359', normal, compile, [''])
+test('T15359a', normal, compile, [''])
+test('T15625', normal, compile, [''])
+test('T15625a', normal, compile, [''])