
recursion-ninja pushed to branch wip/fix-26065 at Glasgow Haskell Compiler / GHC Commits: b75cb447 by Alex Washburn at 2025-08-12T15:35:04-04:00 Improving clarity of T26065 test case output - - - - - 2 changed files: - testsuite/tests/llvm/should_run/T26065.hs - testsuite/tests/llvm/should_run/T26065.stdout Changes: ===================================== testsuite/tests/llvm/should_run/T26065.hs ===================================== @@ -1,6 +1,9 @@ {-# LANGUAGE MagicHash #-} +{-# LANGUAGE ScopedTypeVariables #-} +import Data.Char (toUpper) import GHC.Exts import GHC.Word +import Numeric (showHex) pdep8 :: Word8 -> Word8 -> Word8 pdep8 (W8# a) (W8# b) = W8# (wordToWord8# (pdep8# (word8ToWord# a) (word8ToWord# b))) @@ -34,13 +37,32 @@ pext64 :: Word64 -> Word64 -> Word64 pext64 (W64# a) (W64# b) = W64# (pext64# a b) {-# NOINLINE pext64 #-} +valueSource :: Integral i => i +valueSource = fromInteger 0xA7F7A7F7A7F7A7F7 + +valueMask :: Integral i => i +valueMask = fromInteger 0x5555555555555555 + +printIntrinsicCall :: forall i. Integral i => String -> (i -> i -> i) -> IO () +printIntrinsicCall label f = + let op1 = valueSource + op2 = valueMask + pad s = + let hex :: Integral a => a -> String + hex = flip showHex "" + str = toUpper <$> hex s + len = length $ hex (maxBound :: Word64) + n = length str + in "0x" <> replicate (len - n) '0' <> str + in putStrLn $ unwords [ label, pad op1, pad op2, "=", pad (f op1 op2) ] + main :: IO () main = do - putStr "pdep8:\t" *> print (pdep8 7 3) - putStr "pdep16:\t" *> print (pdep16 7 3) - putStr "pdep32:\t" *> print (pdep32 7 3) - putStr "pdep64:\t" *> print (pdep64 7 3) - putStr "pext8:\t" *> print (pext8 7 3) - putStr "pext16:\t" *> print (pext16 7 3) - putStr "pext32:\t" *> print (pext32 7 3) - putStr "pext64:\t" *> print (pext64 7 3) + printIntrinsicCall "pdep8 " pdep8 + printIntrinsicCall "pdep16" pdep16 + printIntrinsicCall "pdep32" pdep32 + printIntrinsicCall "pdep64" pdep64 + printIntrinsicCall "pext8 " pext8 + printIntrinsicCall "pext16" pext16 + printIntrinsicCall "pext32" pext32 + printIntrinsicCall "pext64" pext64 ===================================== testsuite/tests/llvm/should_run/T26065.stdout ===================================== @@ -1,8 +1,8 @@ -pdep8: 3 -pdep16: 3 -pdep32: 3 -pdep64: 3 -pext8: 3 -pext16: 3 -pext32: 3 -pext64: 3 +pdep8 0x00000000000000F7 0x0000000000000055 = 0x0000000000000015 +pdep16 0x000000000000A7F7 0x0000000000005555 = 0x0000000000005515 +pdep32 0x00000000A7F7A7F7 0x0000000055555555 = 0x0000000044155515 +pdep64 0xA7F7A7F7A7F7A7F7 0x5555555555555555 = 0x4415551544155515 +pext8 0x00000000000000F7 0x0000000000000055 = 0x000000000000000F +pext16 0x000000000000A7F7 0x0000000000005555 = 0x000000000000003F +pext32 0x00000000A7F7A7F7 0x0000000055555555 = 0x0000000000003F3F +pext64 0xA7F7A7F7A7F7A7F7 0x5555555555555555 = 0x000000003F3F3F3F View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b75cb4472fc245142d72aeba75906444... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b75cb4472fc245142d72aeba75906444... You're receiving this email because of your account on gitlab.haskell.org.