[Git][ghc/ghc][master] 2 commits: LLVM: use sse4.2 instead of sse42

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Oct 11 07:56:23 UTC 2024



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


Commits:
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -


5 changed files:

- compiler/GHC/Driver/Pipeline/Execute.hs
- + testsuite/tests/llvm/should_compile/T25019.hs
- + testsuite/tests/llvm/should_compile/T25353.asm
- + testsuite/tests/llvm/should_compile/T25353.hs
- testsuite/tests/llvm/should_compile/all.T


Changes:

=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -987,7 +987,11 @@ llvmOptions llvm_config dflags =
 
         attrs :: String
         attrs = intercalate "," $ mattr
-              ++ ["+sse42"   | isSse4_2Enabled dflags   ]
+              ++ ["+sse4.2"  | isSse4_2Enabled dflags   ]
+              ++ ["+popcnt"  | isSse4_2Enabled dflags   ]
+                   -- LLVM gates POPCNT instructions behind the popcnt flag,
+                   -- while the GHC NCG (as well as GCC, Clang) gates it
+                   -- behind SSE4.2 instead.
               ++ ["+sse2"    | isSse2Enabled platform   ]
               ++ ["+sse"     | isSseEnabled platform    ]
               ++ ["+avx512f" | isAvx512fEnabled dflags  ]


=====================================
testsuite/tests/llvm/should_compile/T25019.hs
=====================================
@@ -0,0 +1 @@
+module T25019 where


=====================================
testsuite/tests/llvm/should_compile/T25353.asm
=====================================
@@ -0,0 +1 @@
+popcnt 
\ No newline at end of file


=====================================
testsuite/tests/llvm/should_compile/T25353.hs
=====================================
@@ -0,0 +1,10 @@
+module Main where
+
+import Data.Bits
+
+{-# NOINLINE foo #-}
+foo :: Int -> Int
+foo x = 1 + popCount x
+
+main :: IO ()
+main = print (foo 42)


=====================================
testsuite/tests/llvm/should_compile/all.T
=====================================
@@ -20,3 +20,5 @@ test('T7575', unless(wordsize(32), skip), compile, [''])
 test('T8131b', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile, [''])
 test('T11649', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile, [''])
 test('T17920fail', cmm_src, compile_fail, ['-no-hs-main'])
+test('T25019', unless((arch('x86_64') or arch('i386')) and have_cpu_feature('sse4_2'),skip), compile, ['-msse4.2'])
+test('T25353', unless((arch('x86_64') or arch('i386')) and have_cpu_feature('sse4_2'),skip), compile_grep_asm, ['hs', True, '-msse4.2'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/09d24d828e48c2588a317e6dad711f8673983703...06ae85071b95376bd1eb354f7cc7901aed45b625

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/09d24d828e48c2588a317e6dad711f8673983703...06ae85071b95376bd1eb354f7cc7901aed45b625
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/20241011/8441b2d3/attachment-0001.html>


More information about the ghc-commits mailing list