[Git][ghc/ghc][master] X86 NCG: allow VXOR at scalar floating-point types

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Nov 16 21:24:21 UTC 2024



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


Commits:
3936bf1b by sheaf at 2024-11-16T16:23:22-05:00
X86 NCG: allow VXOR at scalar floating-point types

The NCG can emit VXOR instructions at scalar floating-point types,
but the pretty-printer would panic instead of emitting the appropriate
VXORPS/VXORPD instructions. This patch rectifies that oversight.

Fixes #25455

- - - - -


4 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/X86/Ppr.hs
=====================================
@@ -1345,9 +1345,11 @@ pprInstr platform i = case i of
        ]
      where
       mem = case fmt of
+        FF32 -> text "vxorps"
+        FF64 -> text "vxorpd"
         VecFormat _ FmtFloat -> text "vxorps"
         VecFormat _ FmtDouble -> text "vxorpd"
-        _ -> pprPanic "GHC.CmmToAsm.X86.Ppr.pprVxor: elementy type must be Float or Double"
+        _ -> pprPanic "GHC.CmmToAsm.X86.Ppr.pprVxor: element type must be Float or Double"
               (ppr fmt)
 
    pprInsert :: Line doc -> Format -> Imm -> Operand -> Reg -> doc


=====================================
testsuite/tests/simd/should_run/T25455.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+
+module Main where
+
+import GHC.Exts
+
+unpackFloatX4 :: FloatX4# -> (Float, Float, Float, Float)
+unpackFloatX4 v = case unpackFloatX4# v of
+  (# a0, a1, a2, a3 #) -> (F# a0, F# a1, F# a2, F# a3)
+
+main :: IO ()
+main = do
+    let v = packFloatX4# (# 0.0#, 1.0#, 2.0#, 3.0# #)
+    print $ unpackFloatX4 v


=====================================
testsuite/tests/simd/should_run/T25455.stdout
=====================================
@@ -0,0 +1 @@
+(0.0,1.0,2.0,3.0)


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -89,3 +89,4 @@ test('T25062_V64'
     , [''])
 
 test('T25169', [], compile_and_run, [''])
+test('T25455', [], compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3936bf1bc37c9f8ea662ed4b57a3a28b5a670c54

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3936bf1bc37c9f8ea662ed4b57a3a28b5a670c54
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/20241116/af3a635c/attachment-0001.html>


More information about the ghc-commits mailing list