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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7185a1f3a02fb92416615e60f2e121c8a77cb827

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

commit 7185a1f3a02fb92416615e60f2e121c8a77cb827
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Wed Oct 31 09:54:08 2012 +0000

    Test Trac #6069

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

 tests/typecheck/should_fail/T6069.hs     |   17 +++++++++++++++++
 tests/typecheck/should_fail/T6069.stderr |   24 ++++++++++++++++++++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 42 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T6069.hs 
b/tests/typecheck/should_fail/T6069.hs
new file mode 100644
index 0000000..8513aab
--- /dev/null
+++ b/tests/typecheck/should_fail/T6069.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE Rank2Types #-}
+
+module T6069 where
+
+import Control.Monad.ST
+import Data.STRef
+
+fourty_two :: forall s. ST s Int
+fourty_two = do
+   x <- newSTRef (42::Int)
+   readSTRef x
+
+f1 = (print . runST) fourty_two -- (1)
+f2 = (print . runST) $ fourty_two -- (2)
+f3 = ((print . runST) $) fourty_two -- (3)
+
+
diff --git a/tests/typecheck/should_fail/T6069.stderr 
b/tests/typecheck/should_fail/T6069.stderr
new file mode 100644
index 0000000..b6ce779
--- /dev/null
+++ b/tests/typecheck/should_fail/T6069.stderr
@@ -0,0 +1,24 @@
+
+T6069.hs:13:15:
+    Couldn't match type `ST s0 Int' with `forall s. ST s b0'
+    Expected type: ST s0 Int -> b0
+      Actual type: (forall s. ST s b0) -> b0
+    In the second argument of `(.)', namely `runST'
+    In the expression: print . runST
+    In the expression: (print . runST) fourty_two
+
+T6069.hs:14:15:
+    Couldn't match type `ST s1 Int' with `forall s. ST s b1'
+    Expected type: ST s1 Int -> b1
+      Actual type: (forall s. ST s b1) -> b1
+    In the second argument of `(.)', namely `runST'
+    In the expression: (print . runST)
+    In the expression: (print . runST) $ fourty_two
+
+T6069.hs:15:16:
+    Couldn't match type `ST s2 Int' with `forall s. ST s b2'
+    Expected type: ST s2 Int -> b2
+      Actual type: (forall s. ST s b2) -> b2
+    In the second argument of `(.)', namely `runST'
+    In the first argument of `($)', namely `(print . runST)'
+    In the expression: (print . runST) $
diff --git a/tests/typecheck/should_fail/all.T 
b/tests/typecheck/should_fail/all.T
index a621298..7e97f72 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -285,3 +285,4 @@ test('T7210', normal, compile_fail, [''])
 test('T6161', normal, compile_fail, [''])
 test('T7368', normal, compile_fail, [''])
 test('T7264', normal, compile_fail, [''])
+test('T6069', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to