[commit: testsuite] master: Fix up cgrun072 a bit (#8250) (c8cd4df)
git at git.haskell.org
git at git.haskell.org
Sun Sep 15 22:18:35 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/c8cd4dfa480bd259bb889c3e679393ffa426abb3/testsuite
>---------------------------------------------------------------
commit c8cd4dfa480bd259bb889c3e679393ffa426abb3
Author: Austin Seipp <austin at well-typed.com>
Date: Sun Sep 15 13:01:38 2013 -0500
Fix up cgrun072 a bit (#8250)
This includes:
* Adding a test for bswap16 with a low byte >= 128
* Also test the byteSwapN functions from GHC.Word, tested both INLINE
and not INLINE, so we test both independent parts: the compilation of
base, and the backend compiling the code *using* base.
* Fix the usage of byteSwapN# primitives in the test, by masking off
* the higher bits when storing the results in Word16/Word32.
Thanks to Reid Barton for the investigation.
Authored-by: Reid Barton <rwbarton at gmail.com>
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
c8cd4dfa480bd259bb889c3e679393ffa426abb3
tests/codeGen/should_run/cgrun072.hs | 55 +++++++++++++++++++++++++-----
tests/codeGen/should_run/cgrun072.stdout | 6 ++++
2 files changed, 52 insertions(+), 9 deletions(-)
diff --git a/tests/codeGen/should_run/cgrun072.hs b/tests/codeGen/should_run/cgrun072.hs
index 1634ac0..403bc49 100644
--- a/tests/codeGen/should_run/cgrun072.hs
+++ b/tests/codeGen/should_run/cgrun072.hs
@@ -1,5 +1,16 @@
{-# LANGUAGE BangPatterns, CPP, MagicHash #-}
+{- Note!
+ If you see output like
+
+ Expected: 48042
+ Actual: 48042
+
+ from this test, it means that the "actual" Word16 (or Word32)
+ has higher bits that are nonzero, which is not allowed!
+ See GHC.Word for an explanation.
+-}
+
module Main ( main ) where
import Data.Bits
@@ -9,15 +20,21 @@ import GHC.Word
#include "MachDeps.h"
main :: IO ()
-main = do putStrLn test_bSwap16
- putStrLn test_bSwap32
- putStrLn test_bSwap64
+main = do putStrLn test_primop_bSwap16
+ putStrLn test_primop_bSwap32
+ putStrLn test_primop_bSwap64
+ putStrLn test_base_bSwap16
+ putStrLn test_base_bSwap32
+ putStrLn test_base_bSwap64
+ putStrLn test'_base_bSwap16
+ putStrLn test'_base_bSwap32
+ putStrLn test'_base_bSwap64
bswap16 :: Word16 -> Word16
-bswap16 (W16# w#) = W16# (byteSwap16# w#)
+bswap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#))
bswap32 :: Word32 -> Word32
-bswap32 (W32# w#) = W32# (byteSwap32# w#)
+bswap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#))
bswap64 :: Word64 -> Word64
bswap64 (W64# w#) = W64# (byteSwap64# w#)
@@ -39,10 +56,25 @@ slowBswap32 w =
slowBswap16 :: Word16 -> Word16
slowBswap16 w = (w `shiftR` 8) .|. (w `shiftL` 8)
-test_bSwap16 = test casesW16 bswap16 slowBswap16
-test_bSwap32 = test casesW32 bswap32 slowBswap32
-test_bSwap64 = test casesW64 bswap64 slowBswap64
+-- Test the primops directly.
+test_primop_bSwap16 = test casesW16 bswap16 slowBswap16
+test_primop_bSwap32 = test casesW32 bswap32 slowBswap32
+test_primop_bSwap64 = test casesW64 bswap64 slowBswap64
+-- Test the wrappers in GHC.Word, inlined.
+-- Inlining matters because it means we are
+-- testing the backend used to run the test,
+-- rather than the backend used to build base.
+test_base_bSwap16 = test casesW16 byteSwap16 slowBswap16
+test_base_bSwap32 = test casesW32 byteSwap32 slowBswap32
+test_base_bSwap64 = test casesW64 byteSwap64 slowBswap64
+
+-- Test the wrappers in GHC.Word, not inlined.
+test'_base_bSwap16 = test' casesW16 byteSwap16 slowBswap16
+test'_base_bSwap32 = test' casesW32 byteSwap32 slowBswap32
+test'_base_bSwap64 = test' casesW64 byteSwap64 slowBswap64
+
+{-# INLINE test #-}
test :: (Eq a, Show a, Num a) => [a] -> (a -> a) -> (a -> a) -> String
test cases fast slow = case failing of
[] -> "OK"
@@ -55,7 +87,12 @@ test cases fast slow = case failing of
expected = map slow cases
actual = map fast cases
-casesW16 = [0xff00,0xf021,0x1234,0x5620,0x5463,0x0000,0xa00f,0x0201,0x2901]
+{-# NOINLINE test' #-}
+test' :: (Eq a, Show a, Num a) => [a] -> (a -> a) -> (a -> a) -> String
+test' = test
+
+casesW16 = [0xff00,0xf021,0x1234,0x5620,0x5463,0x0000,0xa00f,0x0201,0x2901,
+ 0xaabb]
casesW32 = [1480294021,1626858410,2316287658,1246556957,3806579062,65945563,
1521588071,791321966,1355466914,2284998160]
casesW64 = [11004539497957619752,5625461252166958202,1799960778872209546,
diff --git a/tests/codeGen/should_run/cgrun072.stdout b/tests/codeGen/should_run/cgrun072.stdout
index 0eabe36..6bf2504 100644
--- a/tests/codeGen/should_run/cgrun072.stdout
+++ b/tests/codeGen/should_run/cgrun072.stdout
@@ -1,3 +1,9 @@
OK
OK
OK
+OK
+OK
+OK
+OK
+OK
+OK
More information about the ghc-commits
mailing list