summaryrefslogtreecommitdiff
path: root/testsuite/tests/quantified-constraints/T9123.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/quantified-constraints/T9123.hs')
-rw-r--r--testsuite/tests/quantified-constraints/T9123.hs25
1 files changed, 25 insertions, 0 deletions
diff --git a/testsuite/tests/quantified-constraints/T9123.hs b/testsuite/tests/quantified-constraints/T9123.hs
new file mode 100644
index 0000000000..130312b150
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T9123.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE InstanceSigs, RoleAnnotations #-}
+
+module T9123 where
+
+import Data.Coerce
+
+type role Wrap representational nominal
+newtype Wrap m a = Wrap (m a)
+
+class Monad' m where
+ join' :: forall a. m (m a) -> m a
+
+-- Tests the superclass stuff
+instance (forall p q. Coercible p q => Coercible (m p) (m q), Monad' m) => Monad' (Wrap m) where
+ join' :: forall a. Wrap m (Wrap m a) -> Wrap m a
+ join' = coerce @(m (m a) -> m a)
+ @(Wrap m (Wrap m a) -> Wrap m a)
+ join'
+