[commit: testsuite] master: Test #8428 (1420081)

git at git.haskell.org git
Wed Oct 9 20:11:40 UTC 2013


Repository : ssh://git at git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1420081d39aacaa6c8acfc0f31811a4d6c2d1c5c/testsuite

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

commit 1420081d39aacaa6c8acfc0f31811a4d6c2d1c5c
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Wed Oct 9 22:10:50 2013 +0200

    Test #8428


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

1420081d39aacaa6c8acfc0f31811a4d6c2d1c5c
 tests/typecheck/should_fail/T8428.hs     |   13 +++++++++++++
 tests/typecheck/should_fail/T8428.stderr |   10 ++++++++++
 tests/typecheck/should_fail/all.T        |    2 +-
 3 files changed, 24 insertions(+), 1 deletion(-)

diff --git a/tests/typecheck/should_fail/T8428.hs b/tests/typecheck/should_fail/T8428.hs
new file mode 100644
index 0000000..b10bf32
--- /dev/null
+++ b/tests/typecheck/should_fail/T8428.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+
+module T8428 where
+
+import Control.Monad.ST
+
+data IdentityT m a = IdentityT { runIdentityT :: m a }
+
+runIdST :: IdentityT (forall s. ST s) a -> a
+runIdST = runST . runIdentityT
+-- Test formatting in the error message.
+-- In fact this should be rejected as a kind error (#8388)
diff --git a/tests/typecheck/should_fail/T8428.stderr b/tests/typecheck/should_fail/T8428.stderr
new file mode 100644
index 0000000..2351351
--- /dev/null
+++ b/tests/typecheck/should_fail/T8428.stderr
@@ -0,0 +1,10 @@
+
+T8428.hs:11:19:
+    Couldn't match type ?(forall s. ST s) a? with ?forall s. ST s a?
+    Expected type: IdentityT (forall s. ST s) a -> forall s. ST s a
+      Actual type: IdentityT (forall s. ST s) a -> (forall s. ST s) a
+    Relevant bindings include
+      runIdST :: IdentityT (forall s. ST s) a -> a
+        (bound at T8428.hs:11:1)
+    In the second argument of ?(.)?, namely ?runIdentityT?
+    In the expression: runST . runIdentityT
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index bf11f6c..0abc6c7 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -321,4 +321,4 @@ test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail,
 test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
 test('T8306', normal, compile_fail, [''])
 test('T8392a', normal, compile_fail, [''])
-
+test('T8428', normal, compile_fail, [''])




More information about the ghc-commits mailing list