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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3678824ca73b843cb110f8c3814f9f24ddab7cfe

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

commit 3678824ca73b843cb110f8c3814f9f24ddab7cfe
Author: Dimitrios.Vytiniotis <[email protected]>
Date:   Tue Apr 10 13:42:51 2012 +0100

    Adding testcase for Trac 5934

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

 tests/indexed-types/should_fail/T5934.hs     |   12 ++++++++++++
 tests/indexed-types/should_fail/T5934.stderr |    8 ++++++++
 tests/indexed-types/should_fail/all.T        |    2 ++
 3 files changed, 22 insertions(+), 0 deletions(-)

diff --git a/tests/indexed-types/should_fail/T5934.hs 
b/tests/indexed-types/should_fail/T5934.hs
new file mode 100644
index 0000000..2af0b97
--- /dev/null
+++ b/tests/indexed-types/should_fail/T5934.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE RankNTypes, TypeFamilies, KindSignatures #-}
+
+module T5934 where
+import Control.Monad.ST
+
+data Gen s
+type GenST s = Gen (PrimState (ST s))
+
+run :: (forall s. GenST s) -> Int
+run = 0 
+
+type family PrimState (m :: * -> *)
diff --git a/tests/indexed-types/should_fail/T5934.stderr 
b/tests/indexed-types/should_fail/T5934.stderr
new file mode 100644
index 0000000..4ec24d3
--- /dev/null
+++ b/tests/indexed-types/should_fail/T5934.stderr
@@ -0,0 +1,8 @@
+
+T5934.hs:10:7:
+    No instance for (Num ((forall s. GenST s) -> Int))
+      arising from the literal `0'
+    Possible fix:
+      add an instance declaration for (Num ((forall s. GenST s) -> Int))
+    In the expression: 0
+    In an equation for `run': run = 0
diff --git a/tests/indexed-types/should_fail/all.T 
b/tests/indexed-types/should_fail/all.T
index 1f8f99a..d3e691f 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -74,3 +74,5 @@ test('T5439', normal, compile_fail, [''])
 test('T5515', normal, compile_fail, [''])
 test('T5763', expect_broken(5673), compile_fail, [''])
 
+test('T5934', normal, compile_fail, [''])
+



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

Reply via email to