Skip to content
Snippets Groups Projects
Commit 0b0652f1 authored by Ben Gamari's avatar Ben Gamari
Browse files

testsuite/T9430: Fix word-size dependence

Summary: This test was wrong.

Test Plan: Validate

Reviewers: erikd, austin

Subscribers: thomie

Differential Revision: https://phabricator.haskell.org/D1702

GHC Trac Issues: #11294
parent fb5d26d9
No related branches found
No related tags found
No related merge requests found
......@@ -3,8 +3,12 @@
module Main where
import Data.Bits
import GHC.Exts
wordWidth :: Int
wordWidth = finiteBitSize (0 :: Word)
checkI
:: (Int, Int) -- ^ expected results
-> (Int# -> Int# -> (# Int#, Int# #)) -- ^ primop
......@@ -96,10 +100,10 @@ main = do
check "timesWord2# maxBound 1" $ checkW (0, maxBound) timesWord2# maxBound 1
check "timesWord2# 1 maxBound" $ checkW (0, maxBound) timesWord2# 1 maxBound
-- Overflows
check "timesWord2# " $ checkW (1, 0) timesWord2# (2 ^ 63) 2
check "timesWord2# " $ checkW (2, 0) timesWord2# (2 ^ 63) (2 ^ 2)
check "timesWord2# " $ checkW (4, 0) timesWord2# (2 ^ 63) (2 ^ 3)
check "timesWord2# " $ checkW (8, 0) timesWord2# (2 ^ 63) (2 ^ 4)
check "timesWord2# (2^(N-1)) 2" $ checkW (1, 0) timesWord2# (2 ^ (wordWidth-1)) 2
check "timesWord2# (2^(N-1)) 2^2" $ checkW (2, 0) timesWord2# (2 ^ (wordWidth-1)) (2 ^ 2)
check "timesWord2# (2^(N-1)) 2^3" $ checkW (4, 0) timesWord2# (2 ^ (wordWidth-1)) (2 ^ 3)
check "timesWord2# (2^(N-1)) 2^4" $ checkW (8, 0) timesWord2# (2 ^ (wordWidth-1)) (2 ^ 4)
check "timesWord2# maxBound 2" $
checkW (1, maxBound - 1) timesWord2# maxBound 2
check "timesWord2# 2 maxBound" $
......@@ -112,17 +116,17 @@ main = do
check "quotRemWord2# 0 0 1" $ checkW2 (0, 0) quotRemWord2# 0 0 1
check "quotRemWord2# 0 4 2" $ checkW2 (2, 0) quotRemWord2# 0 4 2
check "quotRemWord2# 0 7 3" $ checkW2 (2, 1) quotRemWord2# 0 7 3
check "quotRemWord2# 1 0 (2 ^ 63)" $
checkW2 (2, 0) quotRemWord2# 1 0 (2 ^ 63)
check "quotRemWord2# 1 1 (2 ^ 63)" $
checkW2 (2, 1) quotRemWord2# 1 1 (2 ^ 63)
check "quotRemWord2# 1 0 (2^(N-1))" $
checkW2 (2, 0) quotRemWord2# 1 0 (2 ^ (wordWidth-1))
check "quotRemWord2# 1 1 (2^(N-1))" $
checkW2 (2, 1) quotRemWord2# 1 1 (2 ^ (wordWidth-1))
check "quotRemWord2# 1 0 maxBound" $
checkW2 (1, 1) quotRemWord2# 1 0 maxBound
check "quotRemWord2# 2 0 maxBound" $
checkW2 (2, 2) quotRemWord2# 2 0 maxBound
check "quotRemWord2# 1 maxBound maxBound" $
checkW2 (2, 1) quotRemWord2# 1 maxBound maxBound
check "quotRemWord2# (2 ^ 63) 0 maxBound" $
checkW2 (2 ^ 63, 2 ^ 63) quotRemWord2# (2 ^ 63) 0 maxBound
check "quotRemWord2# (2 ^ 63) maxBound maxBound" $
checkW2 (2 ^ 63 + 1, 2 ^ 63) quotRemWord2# (2 ^ 63) maxBound maxBound
check "quotRemWord2# (2^(N-1)) 0 maxBound" $
checkW2 (2 ^ (wordWidth-1), 2 ^ (wordWidth-1)) quotRemWord2# (2 ^ (wordWidth-1)) 0 maxBound
check "quotRemWord2# (2^(N-1)) maxBound maxBound" $
checkW2 (2 ^ (wordWidth-1) + 1, 2 ^ (wordWidth-1)) quotRemWord2# (2 ^ (wordWidth-1)) maxBound maxBound
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment