recursion-ninja pushed to branch wip/fix-26065 at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • testsuite/tests/llvm/should_run/T26065.hs
    1 1
     {-# LANGUAGE MagicHash #-}
    
    2
    +{-# LANGUAGE ScopedTypeVariables #-}
    
    3
    +import Data.Char (toUpper)
    
    2 4
     import GHC.Exts
    
    3 5
     import GHC.Word
    
    6
    +import Numeric (showHex)
    
    4 7
     
    
    5 8
     pdep8 :: Word8 -> Word8 -> Word8
    
    6 9
     pdep8 (W8# a) (W8# b) = W8# (wordToWord8# (pdep8# (word8ToWord# a) (word8ToWord# b)))
    
    ... ... @@ -34,13 +37,32 @@ pext64 :: Word64 -> Word64 -> Word64
    34 37
     pext64 (W64# a) (W64# b) = W64# (pext64# a b)
    
    35 38
     {-# NOINLINE pext64 #-}
    
    36 39
     
    
    40
    +valueSource :: Integral i => i
    
    41
    +valueSource = fromInteger 0xA7F7A7F7A7F7A7F7
    
    42
    +
    
    43
    +valueMask   :: Integral i => i
    
    44
    +valueMask   = fromInteger 0x5555555555555555
    
    45
    +
    
    46
    +printIntrinsicCall :: forall i. Integral i => String -> (i -> i -> i) -> IO ()
    
    47
    +printIntrinsicCall label f =
    
    48
    +  let op1 = valueSource
    
    49
    +      op2 = valueMask
    
    50
    +      pad s =
    
    51
    +          let hex :: Integral a => a -> String
    
    52
    +              hex = flip showHex ""
    
    53
    +              str = toUpper <$> hex s
    
    54
    +              len = length $ hex (maxBound :: Word64)
    
    55
    +              n   = length str
    
    56
    +          in  "0x" <> replicate (len - n) '0' <> str
    
    57
    +  in  putStrLn $ unwords [ label, pad op1, pad op2, "=", pad (f op1 op2) ]
    
    58
    +
    
    37 59
     main :: IO ()
    
    38 60
     main = do
    
    39
    -  putStr "pdep8:\t"  *> print (pdep8  7 3)
    
    40
    -  putStr "pdep16:\t" *> print (pdep16 7 3)
    
    41
    -  putStr "pdep32:\t" *> print (pdep32 7 3)
    
    42
    -  putStr "pdep64:\t" *> print (pdep64 7 3)
    
    43
    -  putStr "pext8:\t"  *> print (pext8  7 3)
    
    44
    -  putStr "pext16:\t" *> print (pext16 7 3)
    
    45
    -  putStr "pext32:\t" *> print (pext32 7 3)
    
    46
    -  putStr "pext64:\t" *> print (pext64 7 3)
    61
    +  printIntrinsicCall "pdep8 " pdep8
    
    62
    +  printIntrinsicCall "pdep16" pdep16
    
    63
    +  printIntrinsicCall "pdep32" pdep32
    
    64
    +  printIntrinsicCall "pdep64" pdep64
    
    65
    +  printIntrinsicCall "pext8 " pext8
    
    66
    +  printIntrinsicCall "pext16" pext16
    
    67
    +  printIntrinsicCall "pext32" pext32
    
    68
    +  printIntrinsicCall "pext64" pext64

  • testsuite/tests/llvm/should_run/T26065.stdout
    1
    -pdep8:	3
    
    2
    -pdep16:	3
    
    3
    -pdep32:	3
    
    4
    -pdep64:	3
    
    5
    -pext8:	3
    
    6
    -pext16:	3
    
    7
    -pext32:	3
    
    8
    -pext64:	3
    1
    +pdep8  0x00000000000000F7 0x0000000000000055 = 0x0000000000000015
    
    2
    +pdep16 0x000000000000A7F7 0x0000000000005555 = 0x0000000000005515
    
    3
    +pdep32 0x00000000A7F7A7F7 0x0000000055555555 = 0x0000000044155515
    
    4
    +pdep64 0xA7F7A7F7A7F7A7F7 0x5555555555555555 = 0x4415551544155515
    
    5
    +pext8  0x00000000000000F7 0x0000000000000055 = 0x000000000000000F
    
    6
    +pext16 0x000000000000A7F7 0x0000000000005555 = 0x000000000000003F
    
    7
    +pext32 0x00000000A7F7A7F7 0x0000000055555555 = 0x0000000000003F3F
    
    8
    +pext64 0xA7F7A7F7A7F7A7F7 0x5555555555555555 = 0x000000003F3F3F3F