Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/af0b4b830dc4eb0f72f668b0bbec42dd3e4c3ddc

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

commit af0b4b830dc4eb0f72f668b0bbec42dd3e4c3ddc
Author: Simon Peyton Jones <[email protected]>
Date:   Wed May 4 10:09:47 2011 +0100

    Add test for too many/few args in higher order situation

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

 tests/ghc-regress/typecheck/should_fail/all.T      |    1 +
 .../ghc-regress/typecheck/should_fail/tcfail207.hs |    9 +++++++++
 .../typecheck/should_fail/tcfail207.stderr         |   16 ++++++++++++++++
 3 files changed, 26 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/typecheck/should_fail/all.T 
b/tests/ghc-regress/typecheck/should_fail/all.T
index ee290d2..a8706c7 100644
--- a/tests/ghc-regress/typecheck/should_fail/all.T
+++ b/tests/ghc-regress/typecheck/should_fail/all.T
@@ -234,3 +234,4 @@ test('mc22', normal, compile_fail, [''])
 test('mc23', normal, compile_fail, [''])
 test('mc24', normal, compile_fail, [''])
 test('mc25', normal, compile_fail, [''])
+test('tcfail207', normal, compile_fail, [''])
diff --git a/tests/ghc-regress/typecheck/should_fail/tcfail207.hs 
b/tests/ghc-regress/typecheck/should_fail/tcfail207.hs
new file mode 100644
index 0000000..cd57f48
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_fail/tcfail207.hs
@@ -0,0 +1,9 @@
+module Foo where
+
+f :: Int -> [Int] -> [Int]
+-- Want an error message that says 'take' is applied to too many args
+f x = take x []
+
+g :: [Int]
+-- Want an error message that says 'take' is applied to too few args
+g = take 3
diff --git a/tests/ghc-regress/typecheck/should_fail/tcfail207.stderr 
b/tests/ghc-regress/typecheck/should_fail/tcfail207.stderr
new file mode 100644
index 0000000..307b404
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_fail/tcfail207.stderr
@@ -0,0 +1,16 @@
+
+tcfail207.hs:5:7:
+    Couldn't match expected type `[Int] -> [Int]'
+                with actual type `[a0]'
+    In the return type of a call of `take'
+    Probable cause: `take' is applied to too many arguments
+    In the expression: take x []
+    In an equation for `f': f x = take x []
+
+tcfail207.hs:9:5:
+    Couldn't match expected type `[Int]'
+                with actual type `[a0] -> [a0]'
+    In the return type of a call of `take'
+    Probable cause: `take' is applied to too few arguments
+    In the expression: take 3
+    In an equation for `g': g = take 3



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to