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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/6210836d98f6464a0c50438990215abdbc564007

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

commit 6210836d98f6464a0c50438990215abdbc564007
Author: Simon Peyton Jones <[email protected]>
Date:   Sat Jul 23 13:25:36 2011 +0100

    Test Trac #5287

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

 tests/deriving/should_fail/T5287.hs     |    8 ++++++++
 tests/deriving/should_fail/T5287.stderr |   11 +++++++++++
 tests/deriving/should_fail/all.T        |    1 +
 3 files changed, 20 insertions(+), 0 deletions(-)

diff --git a/tests/deriving/should_fail/T5287.hs 
b/tests/deriving/should_fail/T5287.hs
new file mode 100644
index 0000000..5db2d85
--- /dev/null
+++ b/tests/deriving/should_fail/T5287.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-}
+module Bug where
+class A a oops
+data D d = D d
+instance A a oops => Read (D a)
+data E e = E (D e) deriving Read
+
+
diff --git a/tests/deriving/should_fail/T5287.stderr 
b/tests/deriving/should_fail/T5287.stderr
new file mode 100644
index 0000000..608e7aa
--- /dev/null
+++ b/tests/deriving/should_fail/T5287.stderr
@@ -0,0 +1,11 @@
+ghc-stage2.exe: panic! (the 'impossible' happened)
+  (GHC version 7.3.20110721 for i386-unknown-mingw32):
+       solveDerivEqns: probable loop
+    (T5287.hs:6:29-32 main:Bug.$fReadE{v rhW} [e{tv aaR} [tv]] 
base:GHC.Read.Read{tc 2d} [main:Bug.E{tc raM}
+                                                                               
             e{tv aaR} [tv]] = [base:GHC.Read.Read{tc 2d}
+                                                                               
                                  (main:Bug.D{tc raO}
+                                                                               
                                     e{tv aaR} [tv])])
+    [[main:Bug.A{tc raQ} e{tv aaR} [tv] oops{tv alO} [tcs]]]
+
+Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
+
diff --git a/tests/deriving/should_fail/all.T b/tests/deriving/should_fail/all.T
index 8fa5e27..9c362cc 100644
--- a/tests/deriving/should_fail/all.T
+++ b/tests/deriving/should_fail/all.T
@@ -32,4 +32,5 @@ test('drvfail-foldable-traversable1', normal, compile_fail,
 test('T3833', normal, compile_fail, [''])
 test('T3834', normal, compile_fail, [''])
 test('T4528', normal, compile_fail, [''])
+test('T5287', normal, compile_fail, [''])
 



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

Reply via email to