summaryrefslogtreecommitdiff
path: root/testsuite/tests/codeGen/should_run
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-11-02 18:21:46 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-11-06 07:53:42 -0400
commit2800eee24d006cfe5ed224e35e856154ae0cd444 (patch)
tree0b885b48cb1d0b31701a97a6532215e4009414f0 /testsuite/tests/codeGen/should_run
parent20956e5784fe43781d156dd7ab02f0bff4ab41fb (diff)
downloadhaskell-2800eee24d006cfe5ed224e35e856154ae0cd444.tar.gz
Make Word64 use Word64# on every architecture
Diffstat (limited to 'testsuite/tests/codeGen/should_run')
-rw-r--r--testsuite/tests/codeGen/should_run/T9340.hs8
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun071.hs7
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun072.hs4
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun075.hs4
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun076.hs4
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun077.hs14
6 files changed, 3 insertions, 38 deletions
diff --git a/testsuite/tests/codeGen/should_run/T9340.hs b/testsuite/tests/codeGen/should_run/T9340.hs
index 22f5824115..45f791ba73 100644
--- a/testsuite/tests/codeGen/should_run/T9340.hs
+++ b/testsuite/tests/codeGen/should_run/T9340.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE CPP #-}
import Control.Monad
import Data.Bits
@@ -7,8 +6,6 @@ import GHC.Exts
import GHC.Word
import Numeric (showHex)
-#include "MachDeps.h"
-
-- Reference Implementation
-- count trailing zeros
@@ -61,13 +58,8 @@ ctzIUT32 (W# x#) = W# (ctz32# x#)
clzIUT32 (W# x#) = W# (clz32# x#)
ctzIUT64, clzIUT64 :: Word64 -> Word
-#if WORD_SIZE_IN_BITS < 64
ctzIUT64 (W64# x#) = W# (ctz64# x#)
clzIUT64 (W64# x#) = W# (clz64# x#)
-#else
-ctzIUT64 (W64# x#) = W# (ctz64# (wordToWord64# x#))
-clzIUT64 (W64# x#) = W# (clz64# (wordToWord64# x#))
-#endif
main :: IO ()
main = do
diff --git a/testsuite/tests/codeGen/should_run/cgrun071.hs b/testsuite/tests/codeGen/should_run/cgrun071.hs
index c8ee2d17f9..21ee04121b 100644
--- a/testsuite/tests/codeGen/should_run/cgrun071.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun071.hs
@@ -30,12 +30,7 @@ popcnt32 :: Word -> Word
popcnt32 (W# w#) = W# (popCnt32# w#)
popcnt64 :: Word64 -> Word
-popcnt64 (W64# w#) =
-#if SIZEOF_HSWORD == 4
- W# (popCnt64# w#)
-#else
- W# (popCnt# w#)
-#endif
+popcnt64 (W64# w#) = W# (popCnt64# w#)
-- Cribbed from https://gitlab.haskell.org/ghc/ghc/issues/3563
slowPopcnt :: Word -> Word
diff --git a/testsuite/tests/codeGen/should_run/cgrun072.hs b/testsuite/tests/codeGen/should_run/cgrun072.hs
index 729564b631..b97ce56d01 100644
--- a/testsuite/tests/codeGen/should_run/cgrun072.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun072.hs
@@ -37,11 +37,7 @@ bswap32 :: Word32 -> Word32
bswap32 (W32# w#) = W32# (wordToWord32# (byteSwap32# (word32ToWord# w#)))
bswap64 :: Word64 -> Word64
-#if WORD_SIZE_IN_BITS < 64
bswap64 (W64# w#) = W64# (byteSwap64# w#)
-#else
-bswap64 (W64# w#) = W64# (word64ToWord# (byteSwap64# (wordToWord64# w#)))
-#endif
slowBswap64 :: Word64 -> Word64
slowBswap64 w =
diff --git a/testsuite/tests/codeGen/should_run/cgrun075.hs b/testsuite/tests/codeGen/should_run/cgrun075.hs
index 1cac98b2dd..5babde1254 100644
--- a/testsuite/tests/codeGen/should_run/cgrun075.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun075.hs
@@ -36,11 +36,7 @@ instance Pdep Word32 where
pdep (W32# src#) (W32# mask#) = W32# (wordToWord32# (pdep32# (word32ToWord# src#) (word32ToWord# mask#)))
instance Pdep Word64 where
-#if WORD_SIZE_IN_BITS < 64
pdep (W64# src#) (W64# mask#) = W64# (pdep64# src# mask#)
-#else
- pdep (W64# src#) (W64# mask#) = W64# (word64ToWord# (pdep64# (wordToWord64# src#) (wordToWord64# mask#)))
-#endif
class SlowPdep a where
slowPdep :: a -> a -> a
diff --git a/testsuite/tests/codeGen/should_run/cgrun076.hs b/testsuite/tests/codeGen/should_run/cgrun076.hs
index ce26e375d0..4779b5beb8 100644
--- a/testsuite/tests/codeGen/should_run/cgrun076.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun076.hs
@@ -36,11 +36,7 @@ instance Pext Word32 where
pext (W32# src#) (W32# mask#) = W32# (wordToWord32# (pext32# (word32ToWord# src#) (word32ToWord# mask#)))
instance Pext Word64 where
-#if WORD_SIZE_IN_BITS < 64
pext (W64# src#) (W64# mask#) = W64# (pext64# src# mask#)
-#else
- pext (W64# src#) (W64# mask#) = W64# (word64ToWord# (pext64# (wordToWord64# src#) (wordToWord64# mask#)))
-#endif
class SlowPext a where
slowPext :: a -> a -> a
diff --git a/testsuite/tests/codeGen/should_run/cgrun077.hs b/testsuite/tests/codeGen/should_run/cgrun077.hs
index 2058ad7b18..fa224e9eca 100644
--- a/testsuite/tests/codeGen/should_run/cgrun077.hs
+++ b/testsuite/tests/codeGen/should_run/cgrun077.hs
@@ -36,12 +36,7 @@ lzcnt32 :: Word -> Word
lzcnt32 (W# w#) = W# (clz32# w#)
lzcnt64 :: Word64 -> Word
-lzcnt64 (W64# w#) =
-#if SIZEOF_HSWORD == 4
- W# (clz64# w#)
-#else
- W# (clz# w#)
-#endif
+lzcnt64 (W64# w#) = W# (clz64# w#)
lzcnt_slow :: Int -> Word -> Word
lzcnt_slow size x = fromIntegral $ min size $ length $ takeWhile (== False) $ reverse $ map (testBit x) [0 .. size - 1]
@@ -59,12 +54,7 @@ tzcnt32 :: Word -> Word
tzcnt32 (W# w#) = W# (ctz32# w#)
tzcnt64 :: Word64 -> Word
-tzcnt64 (W64# w#) =
-#if SIZEOF_HSWORD == 4
- W# (ctz64# w#)
-#else
- W# (ctz# w#)
-#endif
+tzcnt64 (W64# w#) = W# (ctz64# w#)
tzcnt_slow :: Int -> Word -> Word
tzcnt_slow size x = fromIntegral $ min size $ length $ takeWhile (== False) $ map (testBit x) [0 .. size - 1]