[commit: ghc] master: Regression test for Trac #10390 (c3e6b3a)

git at git.haskell.org git at git.haskell.org
Thu May 7 15:45:39 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c3e6b3ac50e7cc061825d49d06fb4fc81e6d5bc1/ghc

>---------------------------------------------------------------

commit c3e6b3ac50e7cc061825d49d06fb4fc81e6d5bc1
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu May 7 16:46:02 2015 +0100

    Regression test for Trac #10390


>---------------------------------------------------------------

c3e6b3ac50e7cc061825d49d06fb4fc81e6d5bc1
 testsuite/tests/typecheck/should_compile/T10390.hs | 16 ++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 17 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T10390.hs b/testsuite/tests/typecheck/should_compile/T10390.hs
new file mode 100644
index 0000000..e0648c9
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10390.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE RankNTypes #-}
+
+module T10390 where
+
+class ApPair r where
+  apPair :: (forall a . (ApPair a, Num a) => Maybe a) -> Maybe r
+
+instance (ApPair a, ApPair b) => ApPair (a,b) where
+  apPair = apPair'
+
+apPair' :: (ApPair b, ApPair c)
+        => (forall a . (Num a, ApPair a) => Maybe a) -> Maybe (b,c)
+            -- NB constraints in a different order to apPair
+apPair' f =  let (Just a) = apPair f
+                 (Just b) = apPair f
+          in Just $ (a, b)
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 72fe255..562acba 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -453,3 +453,4 @@ test('TcCustomSolverSuper', normal, compile, [''])
 test('T10335', normal, compile, [''])
 test('Improvement', normal, compile, [''])
 test('T10009', normal, compile, [''])
+test('T10390', normal, compile, [''])



More information about the ghc-commits mailing list