Re: [Haskell-cafe] NumberTheory library

As promised, here's the first attempt:
A few small comments about the function "factor" in Prime.hs: o I think you are testing w' * w' < n each time, even when you are repeating factors of the same prime p. You only need to do that when you move to the next p. o You can use divMod (or quotRem) instead of using div and then multiplying. (That's an ancient trick from C. It may not make a difference on modern CPUs.) o You are using the old functional programming trick of artificially creating state with extra function parameters. Nowadays we don't need that in Haskell - it is much simpler just to use the State monad. o I personally would much prefer a function that only returns prime numbers, not -1, 0, or 1. o I think that in most of the places where you fix the type as Int or Integer, you could leave it polymorphic and avoid a lot of coercing. Below is a version of "factor" that implements the above (except the last two, so that I preserve your interface). Regards, Yitz import Control.Monad.State -- ...etc. -- An infinite list of possible prime factors wheel :: Integral a => [a] wheel = iVerySmallPrimes ++ [f + d | d <- [0,iWheelModulus..], f <- wheelSettings] where iWheelModulus = fromIntegral wheelModulus iVerySmallPrimes = map fromIntegral verySmallPrimes wheelSettings = [f | f <- [z,z+2..iWheelModulus+1], null [p | p <- iVerySmallPrimes, f `mod` p == 0]] z = last iVerySmallPrimes + 2 -- |Factorize a number. factor :: Integral a => a -> [a] factor 0 = [0] factor 1 = [1] factor n | n < 0 = -1 : factor (-n) | otherwise = evalState (factorS n) wheel -- Factorize n with wheel as state factorS :: Integral a => a -> State [a] [a] factorS 1 = return [] factorS n = do p <- gets head if p * p > n then return [n] else factorPS n p -- Factorize n at a given prime p factorPS :: Integral a => a -> a -> State [a] [a] factorPS n p | rem == 0 = do ps <- factorPS quot p return (p:ps) | otherwise = do modify tail factorS n where (quot, rem) = n `quotRem` p

G'day all.
Thanks for your suggestions. Some comments...
Quoting Yitzchak Gale
o I think you are testing w' * w' < n each time, even when you are repeating factors of the same prime p. You only need to do that when you move to the next p
Good point, thanks.
o You can use divMod (or quotRem) instead of using div and then multiplying. (That's an ancient trick from C. It may not make a difference on modern CPUs.)
Yup, should have done that to begin with. At the very least, it's no worse than div-plus-multiplying.
o You are using the old functional programming trick of artificially creating state with extra function parameters. Nowadays we don't need that in Haskell - it is much simpler just to use the State monad.
That's true, but it does increase the number of dependencies, as noted in Simon Marlow's recent mail. The MTL might be deprecated soon, replaced by Iavor's library, for example. But your point is well taken. I probably would have done it that way
o I personally would much prefer a function that only returns prime numbers, not -1, 0, or 1.
Sounds like we actually need two functions: factor and primeFactors. (One is, of course, a trivial wrapper around the other.)
o I think that in most of the places where you fix the type as Int or Integer, you could leave it polymorphic and avoid a lot of coercing.
Possibly. I did have performance in mind while doing this. In particular: 1. Ints are usually cheaper than Integers, even when Integers are small enough to fit in an Int, because there's less boxing. In the case of the smallPrimes, for example, everything fits in an Int. Additionally, Ints can be unboxed later if appropriate. 2. Use memoing aggressively (if appropriate), but never use an unbounded amount of memory unless the client has a chance of controlling it. Your wheel implementation is a good example:
-- An infinite list of possible prime factors wheel :: Integral a => [a]
Looking at the type alone: - As it stands, this is not a CAF, and so has to be recomputed every time you use it. - If you did specialise it (perhaps via the SPECIALIZE pragma), it would be a CAF, but then you would need one copy for each specialisation, which (IMO) unnecessarily wastes memory. - Even if that wasn't a problem (say, you only had one specialisation), infinite list CAFs are bad for libraries because they cause space leaks which client code can't control. My original version of Prime had an infinite list CAF of primes, which I ditched in favour of primesUpTo for this very reason. (Well, that and it's faster because you don't need to sieve everything.) The moral of the story is that while I wouldn't think twice about using your solution as-is in a program (it's much more elegant than mine, IMO), in a general-purpose library, you have to tread a bit more carefully. I'll have a go at incorporating your changes. Thanks a lot. And, of course, anyone else with suggestions or patches are welcome to send them to me. Cheers, Andrew Bromage

G'day all.
One more thing...
Quoting Yitzchak Gale
o I think that in most of the places where you fix the type as Int or Integer, you could leave it polymorphic and avoid a lot of coercing.
Even though it looks ugly, converting from an Int to an Integer is really cheap under GHC. Cheers, Andrew Bromage

Hi,
At some point this was the plan, but I am not sure what happened.
I haven't heard of any such plans at the moment, although if you are
interested in the library (which is in many ways quite simillar to
MTL) you can find it at:
http://www.cse.ogi.edu/~diatchki/monadLib
I have been using it for a while, so at least the basics work. I have
done a little profiling, but probably not enough. I don't consider it
to be stable in the sense that I am prepared to change it beyond
fixing bugs. This may change if more people started using it, but as
far as I know I am currently the only user, which also has benfits :-)
Any and all feedback is welcome.
-Iavor
On 5/11/05, Brian Smith
On 5/10/05, ajb@spamcop.net
wrote: The MTL might be deprecated soon, replaced by Iavor's library, for example.
Hi,
Is this just a rumor, or is this really the plan? Where is the best place to get lavor's library?
Thanks, Brian Smith
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, May 11, 2005 at 01:57:58PM -0500, Brian Smith wrote:
On 5/10/05, ajb@spamcop.net
wrote: The MTL might be deprecated soon, replaced by Iavor's library, for example. Is this just a rumor, or is this really the plan? Where is the best place to get lavor's library?
Ack. I use the MTL quite extensivly in most of my projects. I hope it won't disapear from the standard libraries completely. John -- John Meacham - ⑆repetae.net⑆john⑈

G'day all.
Quoting John Meacham
Ack. I use the MTL quite extensivly in most of my projects. I hope it won't disapear from the standard libraries completely.
For the record, I have no information that the MTL will disappear any time soon. However, the proposed roadmap is to move stuff out of hslibs and into cabal, and that may be the eventual fate of the MTL, especially if someone proposes something better for future standardisation. My real point in all this is that using a state monad for the purpose proposed in the number theory library is (IMO) overkill, despite making the code slightly prettier, and introduces dependencies which don't need to be there. My real real point is that the rules for libraries are slightly different than the rules for programs. Cheers, Andrew Bromage

G'day all.
I've finally had a chance to implement some of these changes.
Quoting Yitzchak Gale
o I think you are testing w' * w' < n each time, even when you are repeating factors of the same prime p. You only need to do that when you move to the next p.
Actually, it turns out we only test that when we change wheels, which is not very often. There's still some lambda dropping which could be done, but I'm not sure it's worth it.
o You can use divMod (or quotRem) instead of using div and then multiplying. (That's an ancient trick from C. It may not make a difference on modern CPUs.)
Fixed.
o I personally would much prefer a function that only returns prime numbers, not -1, 0, or 1.
I'd like, if I can, to preserve the property that product is a retraction for factor. I've changed it so that factor 1 = [], but I'm unsure what to do with 0 and negative numbers. I think that factor 0 = [0] is the only reasonable thing to return. As for negative numbers, the two easiest solutions are return -1 as a first factor, or negate the first prime factor returned. Even then, you'd have to return factor (-1) = [-1]. Maybe there should be two functions exposed? Cheers, Andrew Bromage
participants (5)
-
ajb@spamcop.net
-
Brian Smith
-
Iavor Diatchki
-
John Meacham
-
Yitzchak Gale