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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/75dae526dd91c4c68f002495dfcc85b384b44194

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

commit 75dae526dd91c4c68f002495dfcc85b384b44194
Author: Simon Peyton Jones <[email protected]>
Date:   Fri Sep 30 07:57:15 2011 +0100

    Test Trac #5514

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

 tests/typecheck/should_compile/T5514.hs |   13 +++++++++++++
 tests/typecheck/should_compile/all.T    |    1 +
 2 files changed, 14 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/T5514.hs 
b/tests/typecheck/should_compile/T5514.hs
new file mode 100644
index 0000000..71a01ba
--- /dev/null
+++ b/tests/typecheck/should_compile/T5514.hs
@@ -0,0 +1,13 @@
+module T5514 where
+
+class Foo a where
+       foo :: a -> a
+
+instance (Foo a, Foo b) => Foo (a, b) where
+       foo = foo' ()
+
+-- foo' :: () -> b -> b
+foo' es = const id (unitId es)
+
+unitId :: () -> ()
+unitId = id
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index a38bf69..79c50ec 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -361,3 +361,4 @@ test('T2357', normal, compile, [''])
 test('T5481', normal, compile_fail, [''])
 test('T3743', normal, compile, [''])
 test('T5490', normal, compile, [''])
+test('T5514', normal, compile, [''])



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

Reply via email to