Floating-point min/max primops should have consistent behavior across platforms
Summary
The minFloat#
/maxFloat#
primops and friends (proposed in #25120 (closed), implemented as a part of !12860 (closed)) behave differently depending on platforms/backends and optimization flags.
They should have a well-defined semantics regarding on -0
and NaNs.
See also my comment on #25120.
Steps to reproduce
Consider the following program:
{-# LANGUAGE MagicHash #-}
import GHC.Prim
import GHC.Exts
minFloat :: Float -> Float -> Float
minFloat (F# x) (F# y) = F# (minFloat# x y)
minDouble :: Double -> Double -> Double
minDouble (D# x) (D# y) = D# (minDouble# x y)
minFloatN :: Float -> Float -> Float
minFloatN (F# x) (F# y) = F# (minFloat# x y)
{-# NOINLINE minFloatN #-}
minDoubleN :: Double -> Double -> Double
minDoubleN (D# x) (D# y) = D# (minDouble# x y)
{-# NOINLINE minDoubleN #-}
main :: IO ()
main = do
let nanf :: Float
nanf = 0.0 / 0.0
nand :: Double
nand = 0.0 / 0.0
putStrLn "minFloat"
print (minFloat 0.0 (-0.0))
print (minFloat (-0.0) 0.0)
print (minFloat 1.0 nanf)
print (minFloat nanf 1.0)
putStrLn "minDouble"
print (minDouble 0.0 (-0.0))
print (minDouble (-0.0) 0.0)
print (minDouble 1.0 nand)
print (minDouble nand 1.0)
putStrLn "minFloatN"
print (minFloatN 0.0 (-0.0))
print (minFloatN (-0.0) 0.0)
print (minFloatN 1.0 nanf)
print (minFloatN nanf 1.0)
putStrLn "minDoubleN"
print (minDoubleN 0.0 (-0.0))
print (minDoubleN (-0.0) 0.0)
print (minDoubleN 1.0 nand)
print (minDoubleN nand 1.0)
Results on x86_64 (NCG and LLVM):
$ ghc -fforce-recomp -O2 fpminmax.hs
$ ./fpminmax
minFloat
0.0
0.0
1.0
1.0
minDouble
0.0
0.0
1.0
1.0
minFloatN
-0.0
0.0
NaN
1.0
minDoubleN
-0.0
0.0
NaN
1.0
$ ghc -fforce-recomp -O2 -fllvm fpminmax.hs
$ ./fpminmax
minFloat
-0.0
-0.0
1.0
1.0
minDouble
-0.0
-0.0
1.0
1.0
minFloatN
0.0
-0.0
1.0
1.0
minDoubleN
0.0
-0.0
1.0
1.0
Results on AArch64 (NCG and LLVM):
$ uname -m
arm64
$ ghc -fforce-recomp -O2 fpminmax.hs
$ ./fpminmax
minFloat
-0.0
-0.0
NaN
NaN
minDouble
-0.0
-0.0
NaN
NaN
minFloatN
-0.0
-0.0
NaN
NaN
minDoubleN
-0.0
-0.0
NaN
NaN
$ ghc -fforce-recomp -O2 -fllvm fpminmax.hs
$ ./fpminmax
minFloat
-0.0
-0.0
1.0
1.0
minDouble
-0.0
-0.0
1.0
1.0
minFloatN
0.0
-0.0
1.0
1.0
minDoubleN
0.0
-0.0
1.0
1.0
Expected behavior
They should have a consistent behavior.
My proposal is, there should be three variants of min/max primops:
- IEEE 754-2019 minimum/maximum operations
- Honor the sign of zero (
-0 < +0
) - Propagate NaNs
- x86: AVX10.2 will have
VMINMAX{S,P}{H,S,D}
/ needs emulation on current CPUs - AArch64:
FMIN
/FMAX
instructions - WebAssembly:
{f32,f64,f32x4,f64x2}.min/max
instructions
- Honor the sign of zero (
- IEEE 754-2019 minimumNumber/maximumNumber operations
- Honor the sign of zero (
-0 < +0
) - Treat NaNs as "lack of input"
- x86: can be emulated with
VRANGE{S,P}{S,D}
instructions (AVX-512DQ) / AVX10.2 will haveVMINMAX{S,P}{H,S,D}
- AArch64: can be emulated with
FMINNM
/FMAXNM
instructions - RISC-V:
FMIN
/FMAX
instructions
- Honor the sign of zero (
- x86-like operations
min x y = if x < y then x else y
max x y = if y < x then x else y
- Neither commutative nor associative
- e.g.
min 1 (min nan 2) = min 1 2 = 1
,min (min 1 nan) 2 = min nan 2 = 2
- e.g.
- x86:
MIN{S,P}{S,D}
/MAX{S,P}{S,D}
- WebAssembly:
{f32x4,f64x2}.pmin
/{f32x4,f64x2}.pmax
- WebAssembly calls them "pseudo-minimum/maximum"
-- IEEE 754-2019 minimum/maximum
minimumFloat#, maximumFloat# :: Float# -> Float# -> Float#
minimumDouble#, maximumDouble# :: Double# -> Double# -> Double#
-- IEEE 754-2019 minimumNumber/maximumNumber
minimumNumberFloat#, maximumNumberFloat# :: Float# -> Float# -> Float#
minimumNumberDouble#, maximumNumberDouble# :: Double# -> Double# -> Double#
-- x86-like min/max
-- not commutative
pminFloat#, pmaxFloat# :: Float# -> Float# -> Float#
pminDouble#, pmaxDouble# :: Double# -> Double# -> Double#
Environment
- GHC version used: 9.13.20241006 (92f8939a)
- Operating System: Linux/macOS
- System Architecture: x86_64/AArch64