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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d673c4ca3823bff5a712ec3121fa3d00e373c5e3

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

commit d673c4ca3823bff5a712ec3121fa3d00e373c5e3
Author: Ian Lynagh <[email protected]>
Date:   Tue Sep 13 19:23:23 2011 +0100

    Add a test for #3743

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

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

diff --git a/tests/typecheck/should_compile/T3743.hs 
b/tests/typecheck/should_compile/T3743.hs
new file mode 100644
index 0000000..cc8c6cc
--- /dev/null
+++ b/tests/typecheck/should_compile/T3743.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE ImplicitParams, GADTs #-}
+
+module T3743 where
+
+class Foo a
+
+data M where M :: Foo a => a -> M
+
+x :: (?x :: ()) => ()
+x = undefined
+
+-- foo :: (?x :: ()) => M -> ()
+foo y = case y of
+    M _ -> x
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index c3ba163..65fc50a 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -358,3 +358,4 @@ test('T3018', normal, compile, [''])
 test('T5032', normal, compile, [''])
 test('T2357', normal, compile, [''])
 test('T5481', normal, compile, [''])
+test('T3743', normal, compile, [''])



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

Reply via email to