[commit: ghc] master: Validate computed sums in inline array allocation test (d8b3826)

git at git.haskell.org git at git.haskell.org
Tue Mar 11 21:13:24 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/d8b38265d6499914c12e19329203361cb2aa8ea3/ghc

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

commit d8b38265d6499914c12e19329203361cb2aa8ea3
Author: Johan Tibell <johan.tibell at gmail.com>
Date:   Tue Mar 11 22:12:31 2014 +0100

    Validate computed sums in inline array allocation test


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

d8b38265d6499914c12e19329203361cb2aa8ea3
 testsuite/tests/codeGen/should_run/StaticArraySize.hs |    5 ++++-
 1 file changed, 4 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/codeGen/should_run/StaticArraySize.hs b/testsuite/tests/codeGen/should_run/StaticArraySize.hs
index 1052e2d..06c8343 100644
--- a/testsuite/tests/codeGen/should_run/StaticArraySize.hs
+++ b/testsuite/tests/codeGen/should_run/StaticArraySize.hs
@@ -10,6 +10,7 @@
 -- code.
 module Main where
 
+import Control.Monad
 import GHC.Exts
 import GHC.IO
 import Prelude hiding (read)
@@ -47,7 +48,9 @@ main = do
         let marrs = [marr0, marr1, marr2, marr3, marr4, marr5, marr6, marr7,
                      marr8, marr9, marr10, marr11, marr12, marr13, marr14,
                      marr15, marr16, marr17]
-        print `fmap` sumManyArrays marrs
+        total <- sumManyArrays marrs
+        unless (total == 153) $
+            putStrLn "incorrect sum"
         loop (i-1)
 
 sumManyArrays :: [MArray] -> IO Int



More information about the ghc-commits mailing list