summaryrefslogtreecommitdiff
path: root/testsuite/tests/quantified-constraints/T15625a.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/quantified-constraints/T15625a.hs')
-rw-r--r--testsuite/tests/quantified-constraints/T15625a.hs20
1 files changed, 20 insertions, 0 deletions
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