[commit: testsuite] master: Test Trac #7856 (8139121)

Simon Peyton Jones simonpj at microsoft.com
Tue Apr 30 10:51:48 CEST 2013


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

On branch  : master

https://github.com/ghc/testsuite/commit/81391218582bc1b9bf5fbe6506a373e2a0ffcb74

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

commit 81391218582bc1b9bf5fbe6506a373e2a0ffcb74
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Apr 29 17:48:24 2013 +0100

    Test Trac #7856

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

 tests/typecheck/should_fail/T7856.hs     |   19 +++++++++++++++++++
 tests/typecheck/should_fail/T7856.stderr |   11 +++++++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 31 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7856.hs b/tests/typecheck/should_fail/T7856.hs
new file mode 100644
index 0000000..825bc0b
--- /dev/null
+++ b/tests/typecheck/should_fail/T7856.hs
@@ -0,0 +1,19 @@
+module T7856 where
+
+tmp :: String -> IO ()
+tmp = sequence_ lst
+  where lst = [putStrLn "hi"]
+
+-- sequence_ :: Monad m => [m a] -> m ()
+
+{-    m () ~ (->) String (IO ())
+      m a  ~ IO ()
+
+Depends which one gets treated first.
+  m := IO 
+is better than
+  m := (->) String
+It's a bit random which is chosen.
+
+I'll put it in regression suite so we see if it wobbles around.
+-}
\ No newline at end of file
diff --git a/tests/typecheck/should_fail/T7856.stderr b/tests/typecheck/should_fail/T7856.stderr
new file mode 100644
index 0000000..5660188
--- /dev/null
+++ b/tests/typecheck/should_fail/T7856.stderr
@@ -0,0 +1,11 @@
+
+T7856.hs:4:7:
+    Couldn't match expected type ‛String -> IO ()’
+                with actual type ‛IO ()’
+    Possible cause: ‛sequence_’ is applied to too many arguments
+    In the expression: sequence_ lst
+    In an equation for ‛tmp’:
+        tmp
+          = sequence_ lst
+          where
+              lst = [putStrLn "hi"]
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 768b6ed..3c35052 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -306,3 +306,4 @@ test('TcNullaryTCFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''
 test('T7857', normal, compile_fail, [''])
 test('T7778', normal, compile_fail, [''])
 test('T7851', normal, compile_fail, [''])
+test('T7856', normal, compile_fail, [''])





More information about the ghc-commits mailing list