#4344: Better toRational for Float and Double
----------------------------------+-----------------------------------------
Reporter: daniel.is.fischer | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.12.3 | Keywords: toRational, performance
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
----------------------------------+-----------------------------------------
The implementation of `toRational` in the `Real` instances of `Float` and
`Double` is less than ideal.
{{{
instance Real Float where
toRational x = (m%1)*(b%1)^^n
where (m,n) = decodeFloat x
b = floatRadix x
}}}
The propsed implementation of powers for `Rational`s (#4337) would (when
`(^^)` is included) alone yield a great boost, but here we can do even
better.
I have benchmarked three versions of `toRational` against the current
implementation, first, an inlined version of the proposed power
modification:
{{{
{-# SPECIALISE toRat :: Float -> Rational,
Double -> Rational #-}
toRat :: RealFloat a => a -> Rational
toRat x = case decodeFloat x of
(m,e) -> case floatRadix x of
b -> if e < 0
then (m % (b^(negate e)))
else (m * b^e) :% 1
}}}
If the exponent is nonnegative, we need not reduce (even though that
reduction would be comparatively cheap since the denominator is 1, it's
not free).
Next, in GHC.Float there is the condition that the `floatRadix` be 2,
hence we can eliminate the call to `floatRadix` and inline. That allows to
skip the reduction also in some cases where the exponent is negative:
{{{
{-# SPECIALISE toRat2 :: Float -> Rational,
Double -> Rational #-}
toRat2 :: RealFloat a => a -> Rational
toRat2 x = case decodeFloat x of
(m,e) | e < 0 -> if even m
then m % (2 ^ (-e))
else m :% (2 ^ (-e))
| otherwise -> (m * 2^e) :% 1
}}}
Finally, powers of 2 can be more efficiently calculated via bit-shifting
and the test for evenness is usually faster as a bit-test:
{{{
{-# SPECIALISE toRat3 :: Float -> Rational,
Double -> Rational #-}
toRat3 :: RealFloat a => a -> Rational
toRat3 x = case decodeFloat x of
(m,e) | e < 0 -> case 1 `shiftL` (-e) of
!d -> if fromInteger m .&. (1 :: Int)
== 0
then m % d
else m :% d
| otherwise -> (m `shiftL` e) :% 1
}}}
The results vary of course depending on the sample of numbers one
converts, but the trend is clear:
{{{
Current: 100 ms - 123 ms
Inlined: 32 ms - 40 ms
Specialised: 25 ms - 31 ms
Shifting: 15 ms - 23 ms
}}}
Of course, the value of that is limited, the real bottleneck in
`realToFrac` is `fromRational`, which raises the times for the benchmarks
by about 450 ms when added instead of a dummy conversion `Rational ->
Float`. And using `realToFrac` for the conversion `Double -> Float`, per
the rewrite rule, the benchmarks are done in about 1 ms.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4344>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs