Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
03555ed8
by Sylvain Henry at 2025-08-10T22:20:57-04:00
3 changed files:
- compiler/GHC/Cmm/CommonBlockElim.hs
- + testsuite/tests/numeric/should_compile/T26229.hs
- testsuite/tests/numeric/should_compile/all.T
Changes:
... | ... | @@ -29,6 +29,7 @@ import GHC.Utils.Word64 (truncateWord64ToWord32) |
29 | 29 | import Control.Arrow (first, second)
|
30 | 30 | import Data.List.NonEmpty (NonEmpty (..))
|
31 | 31 | import qualified Data.List.NonEmpty as NE
|
32 | +import GHC.Real (infinity,notANumber)
|
|
32 | 33 | |
33 | 34 | -- -----------------------------------------------------------------------------
|
34 | 35 | -- Eliminate common blocks
|
... | ... | @@ -167,7 +168,12 @@ hash_block block = |
167 | 168 | |
168 | 169 | hash_lit :: CmmLit -> Word32
|
169 | 170 | hash_lit (CmmInt i _) = fromInteger i
|
170 | - hash_lit (CmmFloat r _) = truncate r
|
|
171 | + hash_lit (CmmFloat r _)
|
|
172 | + -- handle these special cases as `truncate` fails on non-fractional numbers (#26229)
|
|
173 | + | r == infinity = 9999999
|
|
174 | + | r == -infinity = 9999998
|
|
175 | + | r == notANumber = 6666666
|
|
176 | + | otherwise = truncate r
|
|
171 | 177 | hash_lit (CmmVec ls) = hash_list hash_lit ls
|
172 | 178 | hash_lit (CmmLabel _) = 119 -- ugh
|
173 | 179 | hash_lit (CmmLabelOff _ i) = cvt $ 199 + i
|
1 | +{-# LANGUAGE NegativeLiterals #-}
|
|
2 | + |
|
3 | +module T26229 where
|
|
4 | + |
|
5 | +sqrte2pqiq :: (Floating a, Ord a) => a -> a -> a
|
|
6 | +sqrte2pqiq e qiq -- = sqrt (e*e + qiq)
|
|
7 | + | e < - 1.5097698010472593e153 = -(qiq/e) - e
|
|
8 | + | e < 5.582399551122541e57 = sqrt (e*e + qiq) -- test Infinity#
|
|
9 | + | e < -5.582399551122541e57 = -sqrt (e*e + qiq) -- test -Infinity#
|
|
10 | + | otherwise = (qiq/e) + e
|
|
11 | +{-# SPECIALIZE sqrte2pqiq :: Double -> Double -> Double #-}
|
|
12 | +{-# SPECIALIZE sqrte2pqiq :: Float -> Float -> Float #-} |
... | ... | @@ -22,3 +22,4 @@ test('T15547', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-b |
22 | 22 | test('T23019', normal, compile, ['-O'])
|
23 | 23 | test('T23907', [ when(wordsize(32), expect_broken(23908))], compile, ['-ddump-simpl -O2 -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
|
24 | 24 | test('T24331', normal, compile, ['-O -ddump-simpl -dsuppress-all -dsuppress-uniques -dno-typeable-binds'])
|
25 | +test('T26229', normal, compile, ['-O2']) |