[commit: ghc] master: Add regression tests for #11515 and #12563 (819b9cf)

git at git.haskell.org git at git.haskell.org
Fri May 18 15:52:00 UTC 2018


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

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

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

commit 819b9cfd21a1773091cec4e34716a0fd7c7d05c6
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Fri May 18 11:50:07 2018 -0400

    Add regression tests for #11515 and #12563
    
    Happily, both of these issues appear to have been fixed in GHC 8.2.
    Let's add regression tests for them to ensure that they stay fixed.


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

819b9cfd21a1773091cec4e34716a0fd7c7d05c6
 testsuite/tests/partial-sigs/should_fail/T11515.hs     |  8 ++++++++
 testsuite/tests/partial-sigs/should_fail/T11515.stderr |  5 +++++
 testsuite/tests/partial-sigs/should_fail/all.T         |  1 +
 testsuite/tests/typecheck/should_fail/T12563.hs        |  7 +++++++
 testsuite/tests/typecheck/should_fail/T12563.stderr    | 11 +++++++++++
 testsuite/tests/typecheck/should_fail/all.T            |  1 +
 6 files changed, 33 insertions(+)

diff --git a/testsuite/tests/partial-sigs/should_fail/T11515.hs b/testsuite/tests/partial-sigs/should_fail/T11515.hs
new file mode 100644
index 0000000..2a03e24
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T11515.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE ConstraintKinds, TypeFamilies #-}
+
+module T11515 where
+
+type family ShowSyn a where ShowSyn a = Show a
+
+foo :: (ShowSyn a, _) => a -> String
+foo x = show x
diff --git a/testsuite/tests/partial-sigs/should_fail/T11515.stderr b/testsuite/tests/partial-sigs/should_fail/T11515.stderr
new file mode 100644
index 0000000..2870457
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T11515.stderr
@@ -0,0 +1,5 @@
+
+T11515.hs:7:20: error:
+    • Found type wildcard ‘_’ standing for ‘()’
+      To use the inferred type, enable PartialTypeSignatures
+    • In the type signature: foo :: (ShowSyn a, _) => a -> String
diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T
index 2439f64..9866029 100644
--- a/testsuite/tests/partial-sigs/should_fail/all.T
+++ b/testsuite/tests/partial-sigs/should_fail/all.T
@@ -59,6 +59,7 @@ test('T10615', normal, compile_fail, [''])
 test('T10045', normal, compile_fail, [''])
 test('T10999', normal, compile_fail, [''])
 test('T11122', normal, compile, [''])
+test('T11515', normal, compile_fail, [''])
 test('T11976', normal, compile_fail, [''])
 test('PatBind3', normal, compile_fail, [''])
 test('T12039', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_fail/T12563.hs b/testsuite/tests/typecheck/should_fail/T12563.hs
new file mode 100644
index 0000000..394fa61
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12563.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE RankNTypes #-}
+module T12563 where
+
+foo :: ((forall a. f a) -> f r) -> f r
+foo g = undefined
+
+x = \g -> foo g
diff --git a/testsuite/tests/typecheck/should_fail/T12563.stderr b/testsuite/tests/typecheck/should_fail/T12563.stderr
new file mode 100644
index 0000000..f32e99d
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12563.stderr
@@ -0,0 +1,11 @@
+
+T12563.hs:7:15: error:
+    • Cannot instantiate unification variable ‘p0’
+      with a type involving foralls: (forall a. f0 a) -> f0 r0
+        GHC doesn't yet support impredicative polymorphism
+    • In the first argument of ‘foo’, namely ‘g’
+      In the expression: foo g
+      In the expression: \ g -> foo g
+    • Relevant bindings include
+        g :: p0 (bound at T12563.hs:7:6)
+        x :: p0 -> f0 r0 (bound at T12563.hs:7:1)
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index e4aa682..5a3e733 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -415,6 +415,7 @@ test('T12170a', normal, compile_fail, [''])
 test('T12124', normal, compile_fail, [''])
 test('T12589', normal, compile_fail, [''])
 test('T12529', normal, compile_fail, [''])
+test('T12563', normal, compile_fail, [''])
 test('T12648', normal, compile_fail, [''])
 test('T12729', normal, compile_fail, [''])
 test('T12785b', normal, compile_fail, [''])



More information about the ghc-commits mailing list