Proposal: Better power for Rational

Proposal: A better implementation of powers for Rational Discussion period: Three weeks, until 16^th^ October 2010 (ICFP again) Exponentiation by repeated squaring, as is used in (^) is bad for Rational since on each multiplication a gcd has to be calculated. For well-formed Rationals, the numerator and denominator are known to be coprime, hence all powers of the numerator and denominator are also coprime. To avoid superfluous work, I propose a special power function for Rationals and a rewrite rule to replace calls to (^) for Rational bases by the special function. It might also be beneficial to export the specialised function from Data.Ratio to be used if the rule doesn't fire. Proposed function and rule: ratPow :: Integral a => Rational -> a -> Rational ratPow _ e | e < 0 = error "Negative exponent" ratPow _ 0 = 1 :% 1 ratPow r 1 = r ratPow (0:%y) _ = 0 :% 1 ratPow (x:%1) e = (x^e) :% 1 ratPow (x:%y) e = (x^e) :% (y^e) {-# RULES "power/Rational" (^) = ratPow #-} Like the elimination of `gcd` from recip (#4336), this would yield a great performance boost. Cheers, Daniel

Dear Daniel Thank for your proposals to improve Haskell's numerics. We have long needed someone who was willing to devote some time and attention to this area. Can I interest you in a number of open tickets? #4101: constant folding for (**) #3676: realToFrac conversions #3744: comparisons against minBound and maxBound are not optimised away #3065: quot is sub-optimal #2269: Word type to Double or Float conversions #2271: floor, ceiling, round :: Double -> Int are awesomely slow #1434: slow conversion Double to Int All are accessible as http://hackage.haskell.org/trac/ghc/ticket/4101, etc. All need love. Thanks Simon | -----Original Message----- | From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf | Of Daniel Fischer | Sent: 25 September 2010 01:34 | To: libraries@haskell.org | Subject: Proposal: Better power for Rational | | Proposal: A better implementation of powers for Rational | | Discussion period: Three weeks, until 16^th^ October 2010 (ICFP again)

Simon Peyton-Jones schrieb:
Dear Daniel
Thank for your proposals to improve Haskell's numerics. We have long needed someone who was willing to devote some time and attention to this area.
Can I interest you in a number of open tickets?
#4101: constant folding for (**) #3676: realToFrac conversions #3744: comparisons against minBound and maxBound are not optimised away #3065: quot is sub-optimal #2269: Word type to Double or Float conversions #2271: floor, ceiling, round :: Double -> Int are awesomely slow #1434: slow conversion Double to Int
For the rounding issue I have already written some code for numeric-prelude: http://code.haskell.org/numeric-prelude/src/Algebra/RealRing.hs

| > #4101: constant folding for (**) | > #3676: realToFrac conversions | > #3744: comparisons against minBound and maxBound are not optimised away | > #3065: quot is sub-optimal | > #2269: Word type to Double or Float conversions | > #2271: floor, ceiling, round :: Double -> Int are awesomely slow | > #1434: slow conversion Double to Int | | For the rounding issue I have already written some code for numeric-prelude: | http://code.haskell.org/numeric-prelude/src/Algebra/RealRing.hs Great. I'm not sure which ticket you are referring to, but if you could propose a patch, by email to the libraries list, that would be great Simon

Simon Peyton-Jones schrieb:
| > #4101: constant folding for (**) | > #3676: realToFrac conversions | > #3744: comparisons against minBound and maxBound are not optimised away | > #3065: quot is sub-optimal | > #2269: Word type to Double or Float conversions | > #2271: floor, ceiling, round :: Double -> Int are awesomely slow | > #1434: slow conversion Double to Int | | For the rounding issue I have already written some code for numeric-prelude: | http://code.haskell.org/numeric-prelude/src/Algebra/RealRing.hs
Great. I'm not sure which ticket you are referring to, but if you could propose a patch, by email to the libraries list, that would be great
I'm referring to tickets #2271 and #1434. I implemented round, truncate, floor, ceiling with Int result in terms of double2Int and friends and added RULES for decomposing, e.g. round :: Double -> Int16 into (fromIntegral :: Int -> Int16) . (round :: Double -> Int) However my code is adapted to NumericPrelude's type classes and must be adapted to those of Haskell98's Prelude. This should not be too hard. I'll try to create a patch, however I may need some assistance compiling base libraries. Henning

On Tue, Sep 28, 2010 at 8:23 PM, Henning Thielemann
...however I may need some assistance compiling base libraries.
Just follow the first three points of the GHC build guide: http://hackage.haskell.org/trac/ghc/wiki/Building Bas

On Tue, 28 Sep 2010, Bas van Dijk wrote:
On Tue, Sep 28, 2010 at 8:23 PM, Henning Thielemann
wrote: ...however I may need some assistance compiling base libraries.
Just follow the first three points of the GHC build guide:
I remember I already tried that when I submitted the ticket about round and double2Int years ago. Is there a way to build the base library without building GHC?

| I'm referring to tickets #2271 and #1434. | I implemented round, truncate, floor, ceiling with Int result in terms | of double2Int and friends and added RULES for decomposing, e.g. | round :: Double -> Int16 | into | (fromIntegral :: Int -> Int16) . (round :: Double -> Int) | However my code is adapted to NumericPrelude's type classes and must be | adapted to those of Haskell98's Prelude. This should not be too hard. | I'll try to create a patch, however I may need some assistance compiling | base libraries. Terrific. Maybe work with Daniel Fischer? He's doing closely related stuff as you know. Thanks very much. GHC's numerics need the love. Simon

Henning | I'll try to create a patch, however I may need some assistance compiling base libraries. Thank you. Creating a patch, attaching to a ticket with some rationale, and submitting it to the libraries list, is the best way to push your work over the hill and into the actual code base. I'm sure others will help. If you get stuck, yell! Daniel Fischer is working in this patch too. Simon | -----Original Message----- | From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf | Of Henning Thielemann | Sent: 28 September 2010 19:23 | To: libraries@haskell.org | Subject: Re: Proposal: Better power for Rational | | Simon Peyton-Jones schrieb: | > | > #4101: constant folding for (**) | > | > #3676: realToFrac conversions | > | > #3744: comparisons against minBound and maxBound are not optimised away | > | > #3065: quot is sub-optimal | > | > #2269: Word type to Double or Float conversions | > | > #2271: floor, ceiling, round :: Double -> Int are awesomely slow | > | > #1434: slow conversion Double to Int | > | | > | For the rounding issue I have already written some code for numeric-prelude: | > | http://code.haskell.org/numeric-prelude/src/Algebra/RealRing.hs | > | > Great. I'm not sure which ticket you are referring to, but if you could propose a | patch, by email to the libraries list, that would be great | | I'm referring to tickets #2271 and #1434. | I implemented round, truncate, floor, ceiling with Int result in terms | of double2Int and friends and added RULES for decomposing, e.g. | round :: Double -> Int16 | into | (fromIntegral :: Int -> Int16) . (round :: Double -> Int) | However my code is adapted to NumericPrelude's type classes and must be | adapted to those of Haskell98's Prelude. This should not be too hard. | I'll try to create a patch, however I may need some assistance compiling | base libraries. | | | Henning | _______________________________________________ | Libraries mailing list | Libraries@haskell.org | http://www.haskell.org/mailman/listinfo/libraries

On Monday 04 October 2010 11:57:06, Simon Peyton-Jones wrote:
Henning
| I'll try to create a patch, however I may need some assistance | compiling base libraries.
Thank you. Creating a patch, attaching to a ticket with some rationale, and submitting it to the libraries list, is the best way to push your work over the hill and into the actual code base. I'm sure others will help. If you get stuck, yell!
Daniel Fischer is working in this patch too.
Simon
Since I'm working on GHC.Float anyway, I'll include Henning's rounding etc. code too. Speaking of GHC.Float, there are a few points where I would like some guidance on where to put things. I could of course put everything in GHC.Float, but it's big already and I'd prefer not to clutter it up further. For toRational, to avoid wasting time in gcd, I need an array for the number of trailing 0-bits in a byte. Also, since bit-fiddling of Integers is considerably slower than for fixed width types, I'd need to import GHC.IntWord64 since a Double mantissa won't fit in an Int on 32-bit systems. This could go into GHC.Float or into a GHC.Float.Utils module. For fromRational, I need a fast integerLog2. For that, I need access to the internal representation of Integers when using integer-gmp and an alternative implementation for integer-simple (which would be much slower, but if you use integer-simple, performance probably isn't your foremost concern). I might need a few more odds and ends if special-casing for the results of toRational (whose denominator is a power of 2) proves to be a gain. Putting all the auxiliary stuff in GHC.Float wrapped in #ifdefs is IMO an appalling idea. integerLog2 and more generally integerLogBase are useful enough to be added to GHC.Integer (Int/Word is not yet available, so it'd be the '#' versions, where would the wrappers returning an Int or Word go?). If I need the stuff for special casing, my preferred solution would be to put it in GHC.Integer.Variant.Internals or add a small dedicated module for them to the package. So what's the best place to put stuff?

In general, it's an implementation matter where to put these functions, rather than a major design choice. If one module is getting big and clumsy, then maybe splitting it into two would help. However, as you say we need to think about integer-simple too, so we should perhaps think about adding the same new functions to the 'integer-gmp' and 'integer-simple' packages. Then you would not need #ifdefs in GHC.Float, would you? s | -----Original Message----- | From: daniel.is.fischer@web.de [mailto:daniel.is.fischer@web.de] | Sent: 04 October 2010 15:01 | To: Simon Peyton-Jones; libraries@haskell.org | Subject: Re: Proposal: Better power for Rational | | On Monday 04 October 2010 11:57:06, Simon Peyton-Jones wrote: | > Henning | > | > | I'll try to create a patch, however I may need some assistance | > | compiling base libraries. | > | > Thank you. Creating a patch, attaching to a ticket with some rationale, | > and submitting it to the libraries list, is the best way to push your | > work over the hill and into the actual code base. I'm sure others will | > help. If you get stuck, yell! | > | > Daniel Fischer is working in this patch too. | > | > Simon | | Since I'm working on GHC.Float anyway, I'll include Henning's rounding etc. | code too. | | Speaking of GHC.Float, there are a few points where I would like some | guidance on where to put things. | | I could of course put everything in GHC.Float, but it's big already and I'd | prefer not to clutter it up further. | | For toRational, to avoid wasting time in gcd, I need an array for the | number of trailing 0-bits in a byte. Also, since bit-fiddling of Integers | is considerably slower than for fixed width types, I'd need to import | GHC.IntWord64 since a Double mantissa won't fit in an Int on 32-bit | systems. This could go into GHC.Float or into a GHC.Float.Utils module. | | For fromRational, I need a fast integerLog2. For that, I need access to the | internal representation of Integers when using integer-gmp and an | alternative implementation for integer-simple (which would be much slower, | but if you use integer-simple, performance probably isn't your foremost | concern). I might need a few more odds and ends if special-casing for the | results of toRational (whose denominator is a power of 2) proves to be a | gain. | | Putting all the auxiliary stuff in GHC.Float wrapped in #ifdefs is IMO an | appalling idea. | | integerLog2 and more generally integerLogBase are useful enough to be added | to GHC.Integer (Int/Word is not yet available, so it'd be the '#' versions, | where would the wrappers returning an Int or Word go?). | If I need the stuff for special casing, my preferred solution would be to | put it in GHC.Integer.Variant.Internals or add a small dedicated module for | them to the package. | | So what's the best place to put stuff?

On Monday 04 October 2010 16:47:27, Simon Peyton-Jones wrote:
In general, it's an implementation matter where to put these functions, rather than a major design choice. If one module is getting big and clumsy, then maybe splitting it into two would help.
Yes, I just was a bit uncertain because my favoured way involves several packages, so I thought I'd rather ask for a general okay before producing a number of patches and then get told "Duh, that's not cricket."
However, as you say we need to think about integer-simple too, so we should perhaps think about adding the same new functions to the 'integer-gmp' and 'integer-simple' packages. Then you would not need #ifdefs in GHC.Float, would you?
s
Right, putting the log-related stuff in the integer-* packages would make it work without #ifdefs. I would only need one for toRational if using Int64 instead of Int incurs a performance penalty on 64-bit systems. Does anybody have knowledge about that? Cheers, Daniel

On Sat, Sep 25, 2010 at 02:34:16AM +0200, Daniel Fischer wrote:
ratPow :: Integral a => Rational -> a -> Rational ratPow _ e | e < 0 = error "Negative exponent" ratPow _ 0 = 1 :% 1 ratPow r 1 = r ratPow (0:%y) _ = 0 :% 1 ratPow (x:%1) e = (x^e) :% 1 ratPow (x:%y) e = (x^e) :% (y^e)
Are you deliberately only doing this for Rational, rather than (Ratio t) in general, to avoid differences in behaviour of Integral types? If it was generalised, then we'd presumably want to use % for the final result, so that (2^16 / 3) ^ 2 :: Ratio Int32 is (0 % 1) rather than (0 % 9). Thanks Ian

On Saturday 25 September 2010 14:21:10, Ian Lynagh wrote:
On Sat, Sep 25, 2010 at 02:34:16AM +0200, Daniel Fischer wrote:
ratPow :: Integral a => Rational -> a -> Rational ratPow _ e
| e < 0 = error "Negative exponent"
ratPow _ 0 = 1 :% 1 ratPow r 1 = r ratPow (0:%y) _ = 0 :% 1 ratPow (x:%1) e = (x^e) :% 1 ratPow (x:%y) e = (x^e) :% (y^e)
Are you deliberately only doing this for Rational, rather than (Ratio t) in general, to avoid differences in behaviour of Integral types?
Yes, it would change the behaviour for general t. Take for example t = Word8. (17 % 3) ^ 3 = ((17 % 3) * (17 % 3)) * (17 % 3) = (289 % 9) * (17 % 3) -- reduce numerator mod 256 = (33 % 9) * (17 % 3) -- reduce 33 % 9 = (11 % 3) * (17 % 3) = (187 % 9) (17^3) % (3^3) = 4913 % 27 -- reduce numerator mod 256 = 49 % 27 I'm not principally against changing that behaviour, but changing the results of functions is a big undertaking versus just improving performance. Either behaviour is broken as soon as overflow occurs, they're just broken in different ways.
If it was generalised, then we'd presumably want to use % for the final result, so that (2^16 / 3) ^ 2 :: Ratio Int32 is (0 % 1) rather than (0 % 9).
I wouldn't call (%) directly, with ratPow (x:%y) e = reduce2 (x^e) (y^e) reduce2 = (%) {-# RULES "reduce2/Rational" reduce2 = (:%) :: Integer -> Integer -> Rational #-} We should be able to avoid the superfluous gcd for Rationals (and gcd for Integers is far more costly than for the common fixed-width types).
Thanks Ian
Cheers, Daniel

On Sat, Sep 25, 2010 at 03:36:42PM +0200, Daniel Fischer wrote:
I'm not principally against changing that behaviour, but changing the results of functions is a big undertaking versus just improving performance.
Oh, but as this is done with a rule rather than a class method, it would make the result non-deterministic, depending on whether the rule fires. So yes, restricting it to Rational sounds like the right thing to do. Thanks Ian

If the change is adopted, could the design rational (including why Rational-only) be included as a comment? It's so easily lost! Simon | -----Original Message----- | From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf | Of Ian Lynagh | Sent: 25 September 2010 16:03 | To: libraries@haskell.org | Subject: Re: Proposal: Better power for Rational | | On Sat, Sep 25, 2010 at 03:36:42PM +0200, Daniel Fischer wrote: | > | > I'm not principally against changing that behaviour, but changing the | > results of functions is a big undertaking versus just improving | > performance. | | Oh, but as this is done with a rule rather than a class method, it would | make the result non-deterministic, depending on whether the rule fires. | So yes, restricting it to Rational sounds like the right thing to do. | | | Thanks | Ian | | _______________________________________________ | Libraries mailing list | Libraries@haskell.org | http://www.haskell.org/mailman/listinfo/libraries

On 09/25/10 09:36, Daniel Fischer wrote:
[ratPow :: (Integral b, Integral a) => Ratio b -> a -> Ratio b ratPow ...] ratPow (x:%y) e = reduce2 (x^e) (y^e)
reduce2 = (%) {-# RULES "reduce2/Rational" reduce2 = (:%) :: Integer -> Integer -> Rational #-}
Be careful! To fire that RULE you need to inline or partially specialize ratPow. (re partially specialize, I don't remember if GHC allows specializing to a polymorphic type like Integral a => Rational -> a -> Rational) Anyway this goes rather beyond the proposal. -Isaac

On 09/24/10 20:34, Daniel Fischer wrote:
Proposal: A better implementation of powers for Rational
generally +1
For well-formed Rationals, the numerator and denominator are known to be coprime, hence all powers of the numerator and denominator are also coprime.
Is it worth putting this stuff in the Data.Ratio code comments to explain why what you're doing is valid and useful, or is it already well-commented enough in a general sense about why "gcd" is sometimes necessary, yet expensive?
To avoid superfluous work, I propose a special power function for Rationals and a rewrite rule to replace calls to (^) for Rational bases by the special function. It might also be beneficial to export the specialised function from Data.Ratio to be used if the rule doesn't fire.
Can you do the same for ^^ ? That is, a ratPowCanBeNegative (implement in terms of ratPow, or directly, as you please) and a RULE. (better names would be good if these are going to be exported though! But I don't think they need to be exported, unless hmm, is removing 'gcd' an *asymptotic* speedup for large integers?)
Proposed function and rule:
ratPow :: Integral a => Rational -> a -> Rational ratPow _ e | e< 0 = error "Negative exponent" ratPow _ 0 = 1 :% 1 ratPow r 1 = r ratPow (0:%y) _ = 0 :% 1 ratPow (x:%1) e = (x^e) :% 1 ratPow (x:%y) e = (x^e) :% (y^e)
Wondering why is there an extra case for x:%1 when the x:%y case handles that correctly (albeit slower)? Integer-base ^ does not have this 1-base optimization (maybe that's just because '1' maybe isn't multiplicative identity for general Num, and GHC.Real.^ is written for general Num base, or 1-base isn't common for general exponentiation but in Rationals it's common to have a Rational that's a whole number?), and you don't test for 1-base numerator. I think your choice is sensible enough overall; would like to hear what you think.
Like the elimination of `gcd` from recip (#4336), this would yield a great performance boost.
Did you measure the performance, or is it just obvious? (Either is okay with me.) -Isaac

On Sat, Sep 25, 2010 at 12:05 PM, Isaac Dupree
(better names would be good if these are going to be exported though! But I don't think they need to be exported, unless hmm, is removing 'gcd' an *asymptotic* speedup for large integers?)
Calculating the GCD takes time "O(M(N)*log(N)), where M(N) is the time for multiplying two N-limb numbers" [1,2]. 'ratPow n e' takes at most O(M(N)*log(E)), where N is the size of the result and E is the size of the exponent. So with this optimization we go from O(M(N)*(log(E)+log(N))) to O(M(N)*log(E)). If we assume E to be constant and assume that I didn't do anything wrong, then it's an asymptotic improvement. [1] http://gmplib.org/manual/Greatest-Common-Divisor-Algorithms.html#Greatest-Co... [2] http://gmplib.org/manual/Subquadratic-GCD.html#Subquadratic-GCD -- Felipe.

On Saturday 25 September 2010 17:05:59, Isaac Dupree wrote:
On 09/24/10 20:34, Daniel Fischer wrote:
Proposal: A better implementation of powers for Rational
generally +1
For well-formed Rationals, the numerator and denominator are known to be coprime, hence all powers of the numerator and denominator are also coprime.
Is it worth putting this stuff in the Data.Ratio code comments to explain why what you're doing is valid and useful, or is it already well-commented enough in a general sense about why "gcd" is sometimes necessary, yet expensive?
There are currently not many comments explaining such things there. I guess adding a comment there why the special implementation for Rationals (and not other Ratio t) exists would be a good thing.
To avoid superfluous work, I propose a special power function for Rationals and a rewrite rule to replace calls to (^) for Rational bases by the special function. It might also be beneficial to export the specialised function from Data.Ratio to be used if the rule doesn't fire.
Can you do the same for ^^ ? That is, a ratPowCanBeNegative (implement in terms of ratPow, or directly, as you please) and a RULE.
Sure, that'd be easy. I'm not sure whether it would make much difference. The code for (^^) in GHC.Real is -- | raise a number to an integral power {-# SPECIALISE (^^) :: Rational -> Int -> Rational #-} (^^) :: (Fractional a, Integral b) => a -> b -> a x ^^ n = if n >= 0 then x^n else recip (x^(negate n)) The SPECIALISE pragma is odd, btw. Would a rule for (^^) be likely to fire in cases where the rule for (^) wouldn't? -- testing Yes, it would. So some method of handling (^^) for Rational bases is called for. Question for the experts, what would be more reliable, do a <- [Int, Integer, Word, ... ] [{-# SPECIALISE (^^) :: Rational -> a -> Rational #-}] or {-# RULES "^^/Rational" (^^) = rationalPower #-} rationalPower :: Integral a => Rational -> a -> Rational rationalPower r e | e < 0 = ratPow (recip r) (-e) | otherwise = ratPow r e ? Would specialising ratPow/rationalPower for common exponent types (Int, Integer) give additional benefit?
(better names would be good if these are going to be exported though!
Aye. Unfortunately, I suck at finding good names. Suggestions welcome.
But I don't think they need to be exported, unless hmm, is removing 'gcd' an *asymptotic* speedup for large integers?)
Yes. (Well, beaten by Felipe.)
Proposed function and rule:
ratPow :: Integral a => Rational -> a -> Rational ratPow _ e
| e< 0 = error "Negative exponent"
ratPow _ 0 = 1 :% 1 ratPow r 1 = r ratPow (0:%y) _ = 0 :% 1 ratPow (x:%1) e = (x^e) :% 1 ratPow (x:%y) e = (x^e) :% (y^e)
Wondering why is there an extra case for x:%1 when the x:%y case handles that correctly (albeit slower)?
Well, I'm not sure whether that special case should be removed or a special case for numerator 1 should be added. It would require extensive benchmarking to be sure whether it's an actual improvement. But perhaps
Integer-base ^ does not have this 1-base optimization (maybe that's just because '1' maybe isn't multiplicative identity for general Num, and GHC.Real.^ is written for general Num base,
the special case should be added here. Since x ^ 0 = 1, it seems to be assumed that 1 (or, fromInteger 1) is the multiplicative identity. Then it might also make sense to special case base 0.
or 1-base isn't common for general exponentiation but in Rationals it's common to have a Rational that's a whole number?),
Well, I don't know how common. Of course, a lot of Rationals are created via fromInteger or fromIntegral, so n % 1 is probably overrepresented in code. But if you calculate a lot of x^e for Rational x - and if you do only a handful of exponentiations, small performance differences don't matter anyway -, probably only a small fraction of those are whole numbers (or their reciprocals). So we buy a performance gain for some exponentiations with a small extra cost of a test (== 1) for all exponentiations. Whether one effect outweighs the other, and which one it would be, frankly, I have no idea.
and you don't test for 1-base numerator.
Perhaps I should, but where do I get a large representative sample of Rationals appearing in real code?
I think your choice is sensible enough overall; would like to hear what you think.
Like the elimination of `gcd` from recip (#4336), this would yield a great performance boost.
Did you measure the performance, or is it just obvious? (Either is okay with me.)
Both. I've not done many tests, but all showed a 10× - 20× difference (for larger numbers).
-Isaac
Cheers, Daniel
participants (8)
-
Bas van Dijk
-
Daniel Fischer
-
Felipe Lessa
-
Henning Thielemann
-
Henning Thielemann
-
Ian Lynagh
-
Isaac Dupree
-
Simon Peyton-Jones