[commit: testsuite] master: Add a test for #7734 (4adbade)
Ian Lynagh
igloo at earth.li
Sun Mar 3 18:12:39 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/4adbade9437f48500d2ff2a0a38089e4f329d704
>---------------------------------------------------------------
commit 4adbade9437f48500d2ff2a0a38089e4f329d704
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun Mar 3 16:05:43 2013 +0000
Add a test for #7734
>---------------------------------------------------------------
tests/typecheck/should_fail/T7734.hs | 5 +++++
tests/typecheck/should_fail/T7734.stderr | 18 ++++++++++++++++++
tests/typecheck/should_fail/all.T | 1 +
3 files changed, 24 insertions(+), 0 deletions(-)
diff --git a/tests/typecheck/should_fail/T7734.hs b/tests/typecheck/should_fail/T7734.hs
new file mode 100644
index 0000000..85f83f5
--- /dev/null
+++ b/tests/typecheck/should_fail/T7734.hs
@@ -0,0 +1,5 @@
+
+module T7734 where
+
+x `f` y = x x
+(&) x y = x x
diff --git a/tests/typecheck/should_fail/T7734.stderr b/tests/typecheck/should_fail/T7734.stderr
new file mode 100644
index 0000000..d90d136
--- /dev/null
+++ b/tests/typecheck/should_fail/T7734.stderr
@@ -0,0 +1,18 @@
+
+T7734.hs:4:13:
+ Occurs check: cannot construct the infinite type: t2 ~ t2 -> t1
+ Relevant bindings include
+ f :: (t2 -> t1) -> t -> t1 (bound at T7734.hs:4:1)
+ x :: t2 -> t1 (bound at T7734.hs:4:1)
+ In the first argument of âxâ, namely âxâ
+ In the expression: x x
+ In an equation for âfâ: x `f` y = x x
+
+T7734.hs:5:13:
+ Occurs check: cannot construct the infinite type: t2 ~ t2 -> t1
+ Relevant bindings include
+ & :: (t2 -> t1) -> t -> t1 (bound at T7734.hs:5:1)
+ x :: t2 -> t1 (bound at T7734.hs:5:5)
+ In the first argument of âxâ, namely âxâ
+ In the expression: x x
+ In an equation for â&â: (&) x y = x x
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 0750c57..dfa0668 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -297,3 +297,4 @@ test('T2247', normal, compile_fail, [''])
test('T7609', normal, compile_fail, [''])
test('T7645', normal, compile_fail, [''])
test('T2354', normal, compile_fail, ['-O'])
+test('T7734', normal, compile_fail, [''])
More information about the ghc-commits
mailing list