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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/271b3d3644f383b9e6a0a8e1afd7559da010cef6

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

commit 271b3d3644f383b9e6a0a8e1afd7559da010cef6
Author: Simon Peyton Jones <[email protected]>
Date:   Thu May 5 09:08:11 2011 +0100

    Test Trac #4851

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

 tests/ghc-regress/rebindable/T4851.hs |   12 ++++++++++++
 tests/ghc-regress/rebindable/all.T    |    1 +
 2 files changed, 13 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/rebindable/T4851.hs 
b/tests/ghc-regress/rebindable/T4851.hs
new file mode 100644
index 0000000..38ce452
--- /dev/null
+++ b/tests/ghc-regress/rebindable/T4851.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE Arrows, RebindableSyntax #-}
+module T4851 where
+
+import Prelude hiding ( id, (.) )
+
+import Control.Category        ( Category(..) )
+import Control.Arrow
+
+garbage x =
+  proc b ->
+    do rec (c, d) <- undefined -< (b, d)
+       returnA -< c
diff --git a/tests/ghc-regress/rebindable/all.T 
b/tests/ghc-regress/rebindable/all.T
index 0cb17f5..7df16d4 100644
--- a/tests/ghc-regress/rebindable/all.T
+++ b/tests/ghc-regress/rebindable/all.T
@@ -28,3 +28,4 @@ test('T303', normal, compile, [''])
 test('DoRestrictedM', normal, compile, [''])
 test('DoParamM', reqlib('mtl'), compile_fail, [''])
 test('T5038', normal, compile_and_run, [''])
+test('T4851', normal, compile, [''])



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

Reply via email to