[commit: testsuite] master: Test Trac #7869 (743cab5)
Simon Peyton Jones
simonpj at microsoft.com
Tue Apr 30 16:04:11 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/743cab5865ae0b9820dadc33a692511e0e467b9b
>---------------------------------------------------------------
commit 743cab5865ae0b9820dadc33a692511e0e467b9b
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Apr 30 15:03:49 2013 +0100
Test Trac #7869
>---------------------------------------------------------------
tests/typecheck/should_fail/T7869.hs | 3 +++
tests/typecheck/should_fail/T7869.stderr | 28 ++++++++++++++++++++++++++++
tests/typecheck/should_fail/all.T | 1 +
3 files changed, 32 insertions(+), 0 deletions(-)
diff --git a/tests/typecheck/should_fail/T7869.hs b/tests/typecheck/should_fail/T7869.hs
new file mode 100644
index 0000000..7382847
--- /dev/null
+++ b/tests/typecheck/should_fail/T7869.hs
@@ -0,0 +1,3 @@
+module T7869 where
+
+f = (\x -> f x) :: [a] -> b
diff --git a/tests/typecheck/should_fail/T7869.stderr b/tests/typecheck/should_fail/T7869.stderr
new file mode 100644
index 0000000..bdf814e
--- /dev/null
+++ b/tests/typecheck/should_fail/T7869.stderr
@@ -0,0 +1,28 @@
+
+T7869.hs:3:12:
+ Couldn't match type âbâ with âb1â
+ because type variable âb1â would escape its scope
+ This (rigid, skolem) type variable is bound by
+ an expression type signature: [a1] -> b1
+ at T7869.hs:3:5-27
+ Expected type: [a1] -> b1
+ Actual type: [a] -> b
+ Relevant bindings include f :: [a] -> b (bound at T7869.hs:3:1)
+ In the expression: f x
+ In the expression: (\ x -> f x) :: [a] -> b
+ In an equation for âfâ: f = (\ x -> f x) :: [a] -> b
+
+T7869.hs:3:12:
+ Couldn't match type âaâ with âa1â
+ because type variable âa1â would escape its scope
+ This (rigid, skolem) type variable is bound by
+ an expression type signature: [a1] -> b1
+ at T7869.hs:3:5-27
+ Expected type: [a1] -> b1
+ Actual type: [a] -> b
+ Relevant bindings include
+ f :: [a] -> b (bound at T7869.hs:3:1)
+ x :: [a1] (bound at T7869.hs:3:7)
+ In the expression: f x
+ In the expression: (\ x -> f x) :: [a] -> b
+ In an equation for âfâ: f = (\ x -> f x) :: [a] -> b
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 3c35052..3c0ad61 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -307,3 +307,4 @@ test('T7857', normal, compile_fail, [''])
test('T7778', normal, compile_fail, [''])
test('T7851', normal, compile_fail, [''])
test('T7856', normal, compile_fail, [''])
+test('T7869', normal, compile_fail, [''])
More information about the ghc-commits
mailing list