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

On branch  : ghc-7.4

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

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

commit a1367229f30705adcbdad81dfe3a45944024fa05
Author: Simon Peyton Jones <[email protected]>
Date:   Thu Jan 12 18:19:41 2012 +0000

    Test Trac #5658b

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

 tests/simplCore/should_compile/Makefile            |    5 +++++
 tests/simplCore/should_compile/T5658b.hs           |   17 +++++++++++++++++
 .../should_compile/T5658b.stdout}                  |    0 
 tests/simplCore/should_compile/all.T               |    4 ++++
 4 files changed, 26 insertions(+), 0 deletions(-)

diff --git a/tests/simplCore/should_compile/Makefile 
b/tests/simplCore/should_compile/Makefile
index 913d362..b2815ff 100644
--- a/tests/simplCore/should_compile/Makefile
+++ b/tests/simplCore/should_compile/Makefile
@@ -7,6 +7,11 @@ T3055:
        '$(TEST_HC)' $(TEST_HC_OPTS) -O -c T3055.hs -ddump-simpl > T3055.simpl
        grep 'I# (-28)' T3055.simpl | sed 's/.*\(I# (-28)\).*/\1/'
 
+T5658b:
+       $(RM) -f T5658b.o T5658b.hi 
+       '$(TEST_HC)' $(TEST_HC_OPTS) -O -c T5658b.hs -ddump-simpl | grep 
--count indexIntArray
+# Trac 5658 meant that there were three calls to indexIntArray instead of two
+
 T3772:
        $(RM) -f T3772*.hi T3772*.o
        '$(TEST_HC)' $(TEST_HC_OPTS) -c -O T3772_A.hs 
diff --git a/tests/simplCore/should_compile/T5658b.hs 
b/tests/simplCore/should_compile/T5658b.hs
new file mode 100644
index 0000000..2c1c9ca
--- /dev/null
+++ b/tests/simplCore/should_compile/T5658b.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE MagicHash, BangPatterns #-}
+module T5658b where
+import GHC.Prim
+
+foo :: ByteArray# -> ByteArray# -> Int# -> Int# -> Bool
+foo xs ys m n = go 0# 0#
+  where
+    go i j = case i >=# m of
+      False -> let !x = indexIntArray# xs i in
+        case j >=# n of
+          False -> case x ==# indexIntArray# ys j of
+            False -> False
+            True  -> go (i +# 1#) (j +# 1#)
+          True -> False
+      True -> case j >=# n of
+        False -> let !y = indexIntArray# ys i in False
+        True -> True
diff --git a/tests/concurrent/should_run/3279.stdout 
b/tests/simplCore/should_compile/T5658b.stdout
similarity index 100%
copy from tests/concurrent/should_run/3279.stdout
copy to tests/simplCore/should_compile/T5658b.stdout
diff --git a/tests/simplCore/should_compile/all.T 
b/tests/simplCore/should_compile/all.T
index ce6549c..fb1b58f 100644
--- a/tests/simplCore/should_compile/all.T
+++ b/tests/simplCore/should_compile/all.T
@@ -134,3 +134,7 @@ test('simpl021',
      run_command,
      ['$MAKE -s --no-print-directory simpl021'])
 test('T5327', normal, run_command, ['$MAKE -s --no-print-directory T5327'])
+test('T5658b',
+     normal,
+     run_command,
+     ['$MAKE -s --no-print-directory T5658b'])



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

Reply via email to