[Git][ghc/ghc][master] Handle non-fractional CmmFloats in Cmm's CBE (#26229)

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 03555ed8 by Sylvain Henry at 2025-08-10T22:20:57-04:00 Handle non-fractional CmmFloats in Cmm's CBE (#26229) Since f8d9d016305be355f518c141f6c6d4826f2de9a2, toRational for Float and Double converts float's infinity and NaN into Rational's infinity and NaN (respectively 1%0 and 0%0). Cmm CommonBlockEliminator hashing function needs to take these values into account as they can appear as literals now. See added testcase. - - - - - 3 changed files: - compiler/GHC/Cmm/CommonBlockElim.hs - + testsuite/tests/numeric/should_compile/T26229.hs - testsuite/tests/numeric/should_compile/all.T Changes: ===================================== compiler/GHC/Cmm/CommonBlockElim.hs ===================================== @@ -29,6 +29,7 @@ import GHC.Utils.Word64 (truncateWord64ToWord32) import Control.Arrow (first, second) import Data.List.NonEmpty (NonEmpty (..)) import qualified Data.List.NonEmpty as NE +import GHC.Real (infinity,notANumber) -- ----------------------------------------------------------------------------- -- Eliminate common blocks @@ -167,7 +168,12 @@ hash_block block = hash_lit :: CmmLit -> Word32 hash_lit (CmmInt i _) = fromInteger i - hash_lit (CmmFloat r _) = truncate r + hash_lit (CmmFloat r _) + -- handle these special cases as `truncate` fails on non-fractional numbers (#26229) + | r == infinity = 9999999 + | r == -infinity = 9999998 + | r == notANumber = 6666666 + | otherwise = truncate r hash_lit (CmmVec ls) = hash_list hash_lit ls hash_lit (CmmLabel _) = 119 -- ugh hash_lit (CmmLabelOff _ i) = cvt $ 199 + i ===================================== testsuite/tests/numeric/should_compile/T26229.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE NegativeLiterals #-} + +module T26229 where + +sqrte2pqiq :: (Floating a, Ord a) => a -> a -> a +sqrte2pqiq e qiq -- = sqrt (e*e + qiq) + | e < - 1.5097698010472593e153 = -(qiq/e) - e + | e < 5.582399551122541e57 = sqrt (e*e + qiq) -- test Infinity# + | e < -5.582399551122541e57 = -sqrt (e*e + qiq) -- test -Infinity# + | otherwise = (qiq/e) + e +{-# SPECIALIZE sqrte2pqiq :: Double -> Double -> Double #-} +{-# SPECIALIZE sqrte2pqiq :: Float -> Float -> Float #-} ===================================== testsuite/tests/numeric/should_compile/all.T ===================================== @@ -22,3 +22,4 @@ test('T15547', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-b test('T23019', normal, compile, ['-O']) test('T23907', [ when(wordsize(32), expect_broken(23908))], compile, ['-ddump-simpl -O2 -dsuppress-all -dno-typeable-binds -dsuppress-uniques']) test('T24331', normal, compile, ['-O -ddump-simpl -dsuppress-all -dsuppress-uniques -dno-typeable-binds']) +test('T26229', normal, compile, ['-O2']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/03555ed8bad1cc3dc0bf5744bb0924bf... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/03555ed8bad1cc3dc0bf5744bb0924bf... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)