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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/6e301a83e5162008b0fe7a63b0f3a7beaea112af

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

commit 6e301a83e5162008b0fe7a63b0f3a7beaea112af
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Tue Jan 8 23:46:37 2013 +0000

    Test Trac #7279

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

 tests/typecheck/should_fail/T7279.hs     |    6 ++++++
 tests/typecheck/should_fail/T7279.stderr |   10 ++++++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 17 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7279.hs 
b/tests/typecheck/should_fail/T7279.hs
new file mode 100644
index 0000000..f1cc9d7
--- /dev/null
+++ b/tests/typecheck/should_fail/T7279.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE UndecidableInstances #-}
+module T7279 where
+
+data T a = MkT
+
+instance (Eq a, Show b) => Eq (T a)
diff --git a/tests/typecheck/should_fail/T7279.stderr 
b/tests/typecheck/should_fail/T7279.stderr
new file mode 100644
index 0000000..6af478e
--- /dev/null
+++ b/tests/typecheck/should_fail/T7279.stderr
@@ -0,0 +1,10 @@
+
+T7279.hs:6:10:
+    Could not deduce (Show b0)
+      arising from the ambiguity check for an instance declaration
+    from the context (Eq a, Show b)
+      bound by an instance declaration: (Eq a, Show b) => Eq (T a)
+      at T7279.hs:6:10-35
+    The type variable `b0' is ambiguous
+    In the ambiguity check for: forall a b. (Eq a, Show b) => Eq (T a)
+    In the instance declaration for `Eq (T a)'
diff --git a/tests/typecheck/should_fail/all.T 
b/tests/typecheck/should_fail/all.T
index bbf6eb6..a4d0216 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -292,3 +292,4 @@ test('T7453', normal, compile_fail, [''])
 test('T7525', normal, compile_fail, [''])
 test('T7368a', normal, compile_fail, [''])
 test('T7545', normal, compile_fail, [''])
+test('T7279', normal, compile_fail, [''])



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

Reply via email to