x86_64: FMA primop generates wrong result
Summary
On x86, FMA primop generates wrong result with -mfma -O1
.
Steps to reproduce
Compile the following code with ghc -fforce-recomp -O1 -mfma TwoProdFMA.hs
:
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
import GHC.Exts
twoProductFloat# :: Float# -> Float# -> (# Float#, Float# #)
twoProductFloat# x y = let !r = x `timesFloat#` y
in (# r, fmsubFloat# x y r #)
{-# NOINLINE twoProductFloat# #-}
twoProductDouble# :: Double# -> Double# -> (# Double#, Double# #)
twoProductDouble# x y = let !r = x *## y
in (# r, fmsubDouble# x y r #)
{-# NOINLINE twoProductDouble# #-}
main :: IO ()
main = do
print $ case twoProductFloat# 2.0# 3.0# of (# r, s #) -> (F# r, F# s)
print $ case twoProductDouble# 2.0## 3.0## of (# r, s #) -> (D# r, D# s)
The result is wrong:
$ ghc -fforce-recomp -mfma -O1 TwoProdFMA.hs
$ ./TwoProdFMA
(6.0,-2.0)
(6.0,-2.0)
Expected behavior
The expected result is:
(6.0,0.0)
(6.0,0.0)
Environment
- GHC version used: 9.8.2, master (b4cae4ec)
- Operating System: Linux
- System Architecture: x86-64