[Git][ghc/ghc][master] x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2#

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Jan 17 16:19:00 UTC 2025



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
5a8f35bd by ARATA Mizuki at 2025-01-17T11:17:49-05:00
x86 NCG: Use correct format for MOVD in the implementation of unpackInt64X2#

MOVD takes the input format.

Fixes #25658

- - - - -


4 changed files:

- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- + testsuite/tests/simd/should_run/T25658.hs
- + testsuite/tests/simd/should_run/T25658.stdout
- testsuite/tests/simd/should_run/all.T


Changes:

=====================================
compiler/GHC/CmmToAsm/X86/CodeGen.hs
=====================================
@@ -1818,10 +1818,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps
       let code dst =
             case lit of
               CmmInt 0 _ -> exp `snocOL`
-                            (MOVD II64 (OpReg r) (OpReg dst))
+                            (MOVD FF64 (OpReg r) (OpReg dst))
               CmmInt 1 _ -> exp `snocOL`
                             (MOVHLPS fmt r tmp) `snocOL`
-                            (MOVD II64 (OpReg tmp) (OpReg dst))
+                            (MOVD FF64 (OpReg tmp) (OpReg dst))
               _          -> panic "Error in offset while unpacking"
       return (Any II64 code)
     vector_int64x2_extract_sse2 _ offset


=====================================
testsuite/tests/simd/should_run/T25658.hs
=====================================
@@ -0,0 +1,19 @@
+{-# LANGUAGE MagicHash, UnboxedTuples, ExtendedLiterals #-}
+import GHC.Int
+import GHC.Prim
+
+test :: (Int64X2# -> Int64X2# -> Int64X2#) -> IO ()
+test f = do
+  let a = packInt64X2# (# 0#Int64, 11#Int64 #)
+      b = packInt64X2# (# 22#Int64, 33#Int64 #)
+      c = f a b
+      (# x0, x1 #) = unpackInt64X2# a
+      (# y0, y1 #) = unpackInt64X2# b
+      (# z0, z1 #) = unpackInt64X2# c
+  putStrLn $ "a = " ++ show (I64# x0, I64# x1)
+  putStrLn $ "b = " ++ show (I64# y0, I64# y1)
+  putStrLn $ "c = " ++ show (I64# z0, I64# z1)
+{-# NOINLINE test #-}
+
+main :: IO ()
+main = test (\a _ -> a)


=====================================
testsuite/tests/simd/should_run/T25658.stdout
=====================================
@@ -0,0 +1,3 @@
+a = (0,11)
+b = (22,33)
+c = (0,11)


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -25,6 +25,8 @@ test('word16x8_basic_baseline', [], compile_and_run, [''])
 test('word32x4_basic_baseline', [], compile_and_run, [''])
 test('word64x2_basic_baseline', [], compile_and_run, [''])
 
+test('T25658', [], compile_and_run, ['']) # #25658 is a bug with SSE2 code generation
+
 # Ensure we set the CPU features we have available.
 #
 # This is especially important with the LLVM backend, as LLVM can otherwise



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a8f35bd5d9735d7846a53bc9d08d8eeb67bccb5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a8f35bd5d9735d7846a53bc9d08d8eeb67bccb5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250117/c581718a/attachment-0001.html>


More information about the ghc-commits mailing list