diff options
author | Reid Barton <rwbarton@gmail.com> | 2014-08-09 19:20:53 -0400 |
---|---|---|
committer | Reid Barton <rwbarton@gmail.com> | 2014-08-09 19:20:53 -0400 |
commit | b7b7633dfc350322756b8735a4d7c9a5c42d1721 (patch) | |
tree | 29b68d6d1e19a1989884f33c47e6767350770e5d /testsuite/tests/numeric | |
parent | 8e01ca6872c1db9b1b2f7c0ba05d01b1c3436307 (diff) | |
download | haskell-b7b7633dfc350322756b8735a4d7c9a5c42d1721.tar.gz |
Add a test for plusWord2#, addIntC#, subIntC#
Diffstat (limited to 'testsuite/tests/numeric')
-rw-r--r-- | testsuite/tests/numeric/should_run/CarryOverflow.hs | 89 | ||||
-rw-r--r-- | testsuite/tests/numeric/should_run/CarryOverflow.stdout | 1 | ||||
-rw-r--r-- | testsuite/tests/numeric/should_run/all.T | 1 |
3 files changed, 91 insertions, 0 deletions
diff --git a/testsuite/tests/numeric/should_run/CarryOverflow.hs b/testsuite/tests/numeric/should_run/CarryOverflow.hs new file mode 100644 index 0000000000..f83c1cf15c --- /dev/null +++ b/testsuite/tests/numeric/should_run/CarryOverflow.hs @@ -0,0 +1,89 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} + +import GHC.Prim +import GHC.Word +import GHC.Exts + +import Control.Monad +import Data.Bits +import Data.List +import System.Exit + +allEqual :: Eq a => [a] -> Bool +allEqual [] = error "allEqual: nothing to compare" +allEqual (x:xs) = all (== x) xs + +testWords :: [Word] +testWords = map head . group . sort $ + concatMap (\w -> [w - 1, w, w + 1]) $ + concatMap (\w -> [w, maxBound - w]) $ + trailingOnes ++ randoms + where trailingOnes = takeWhile (/= 0) $ iterate (`div` 2) $ maxBound + -- What would a Haskell program be without some Fibonacci numbers? + randoms = take 40 $ drop 100 fibs + fibs = 0 : 1 : zipWith (+) fibs (tail fibs) + + +wordSizeInBits :: Int +wordSizeInBits = length $ takeWhile (/= 0) $ iterate (`div` 2) (maxBound :: Word) + + +-- plusWord2# (Word# carry) + +ways_plusWord2# :: [Word -> Word -> Bool] +ways_plusWord2# = [ltTest, integerTest, primopTest] + where ltTest x y = + let r = x + y in r < x + integerTest x y = + let r = fromIntegral x + fromIntegral y :: Integer + in r > fromIntegral (maxBound :: Word) + primopTest (W# x) (W# y) = case plusWord2# x y of + (# 0##, _ #) -> False + (# 1##, _ #) -> True + _ -> error "unexpected result from plusWord2#" + +-- addIntC# (Int# addition overflow) + +ways_addIntC# :: [Int -> Int -> Bool] +ways_addIntC# = [ltTest, integerTest, highBitTest, primopTest] + where ltTest x y = + let r = x + y in (y > 0 && r < x) || (y < 0 && r > x) + integerTest x y = + let r = fromIntegral x + fromIntegral y :: Integer + in r < fromIntegral (minBound :: Int) || r > fromIntegral (maxBound :: Int) + highBitTest x y = + let r = x + y in testBit ((x `xor` r) .&. (y `xor` r)) (wordSizeInBits - 1) + primopTest (I# x) (I# y) = case addIntC# x y of + (# _, 0# #) -> False + _ -> True + +-- subIntC# (Int# subtraction overflow) + +ways_subIntC# :: [Int -> Int -> Bool] +ways_subIntC# = [ltTest, integerTest, highBitTest, primopTest] + where ltTest x y = + let r = x - y in (y > 0 && r > x) || (y < 0 && r < x) + integerTest x y = + let r = fromIntegral x - fromIntegral y :: Integer + in r < fromIntegral (minBound :: Int) || r > fromIntegral (maxBound :: Int) + highBitTest x y = + let r = x - y in testBit ((x `xor` r) .&. complement (y `xor` r)) (wordSizeInBits - 1) + primopTest (I# x) (I# y) = case subIntC# x y of + (# _, 0# #) -> False + _ -> True + +runTest :: Show a => String -> [a -> a -> Bool] -> a -> a -> IO () +runTest label ways x y = do + let results = map (\f -> f x y) ways + unless (allEqual results) $ do + putStrLn $ "Failed (" ++ label ++ "): " ++ show (x,y) ++ " " ++ show results + exitWith (ExitFailure 1) + +main :: IO () +main = do + forM_ testWords $ \x -> + forM_ testWords $ \y -> do + runTest "ways_plusWord2#" ways_plusWord2# x y + runTest "ways_addIntC#" ways_addIntC# (fromIntegral x) (fromIntegral y) + runTest "ways_subIntC#" ways_subIntC# (fromIntegral x) (fromIntegral y) + putStrLn "Passed" diff --git a/testsuite/tests/numeric/should_run/CarryOverflow.stdout b/testsuite/tests/numeric/should_run/CarryOverflow.stdout new file mode 100644 index 0000000000..863339fb8c --- /dev/null +++ b/testsuite/tests/numeric/should_run/CarryOverflow.stdout @@ -0,0 +1 @@ +Passed diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 3953fe6339..72c8e6a74a 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -62,3 +62,4 @@ test('T7014', test('T7233', normal, compile_and_run, ['']) test('NumDecimals', normal, compile_and_run, ['']) test('T8726', normal, compile_and_run, ['']) +test('CarryOverflow', omit_ways(['ghci']), compile_and_run, ['']) |