
Hi, I defined several functions for calculating the number of trailing zero's of n! tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5 tm1 n = sum . takeWhile(>0) . map (div n . (5^)) $ [1..] tm2 n = sum . takeWhile(>0) . map (div n) $ iterate ((*)5) 5 tm3 = sum . takeWhile(>0) . flip map (iterate ((*)5) 5) . div Questions: Which one is the most elegant one generally speaking? Which one is most natural in Haskell? Is there more 'beauty' to possible? My personal choice is 'tm'. I like 'tm3' (a revised version of tm2) in terms of pointlessness and not having a 'where', but I think it's a bit contrived because of the 'flip'. Comments? Thanks @@i

On Aug 24, 2007, at 9:18 , Arie Groeneveld wrote:
Hi,
I defined several functions for calculating the number of trailing zero's of n!
tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5
tm1 n = sum . takeWhile(>0) . map (div n . (5^)) $ [1..] tm2 n = sum . takeWhile(>0) . map (div n) $ iterate ((*)5) 5 tm3 = sum . takeWhile(>0) . flip map (iterate ((*)5) 5) . div
Questions:
Which one is the most elegant one generally speaking? Which one is most natural in Haskell? Is there more 'beauty' to possible?
My personal choice is 'tm'. I like 'tm3' (a revised version of tm2) in terms of pointlessness and not having a 'where', but I think it's a bit contrived because of the 'flip'.
Comments?
Here's a much more inefficient version, but it has the merit of being very easy to understand: tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n] /Björn

Bjorn Bringert wrote:
Here's a much more inefficient version, but it has the merit of being very easy to understand:
tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
You're rigth. I came up with that one too the first time. But for large value's of n it takes too much time. You may improve that (time) by using another product formula: *Main> length $ takeWhile (=='0') $ reverse $ show $ foldl' (*) 1 [1..30000] 7498 (0.96 secs, 790685000 bytes) *Main> length $ takeWhile (=='0') $ reverse $ show $ product [1..30000] 7498 (4.05 secs, 792259140 bytes) But: *Main> tm 30000 7498 (0.00 secs, 524924 bytes) Thanks @@i

"Marc A. Ziegert"
tm_parallelizable_v1 = \n -> sum . takeWhile (>0) $ map (div n) fives where fives = iterate (*5) 1 tm_improved_v1 n = sum . takeWhile (>0) $ iterate (div `flip` 5) (div n 5) tm_fastestIMHO n = let m=div n 5 in if m<5 then m else m+tm_fastestIMHO m
Henning Thielemann
tm4 = sum . takeWhile(>0) . tail . iterate (flip div 5)
Bjorn Bringert
tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
Arie Groeneveld
tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5 tm1 n = sum . takeWhile(>0) . map (div n . (5^)) $ [1..] tm2 n = sum . takeWhile(>0) . map (div n) $ iterate ((*)5) 5 tm3 = sum . takeWhile(>0) . flip map (iterate ((*)5) 5) . div

Bjorn Bringert wrote:
Here's a much more inefficient version, but it has the merit of being very easy to understand:
tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
Be careful with types - use Data.List.genericLength here instead of length. Otherwise, tm_silly n is wrong for n >= 13 (on my 32-bit machine) due to round-off error in the Int type. Here is another implementation:
base5 n | n < 1 = [] | otherwise = let (q, r) = n `divMod` 5 in r : base5 q
tm6 = sum . zipWith (*) [(5^k-1)`div`4 | k <- [0..]] . base5
Regards, Yitz

2007/8/26, Yitzchak Gale
Bjorn Bringert wrote:
Here's a much more inefficient version, but it has the merit of being very easy to understand:
tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
Be careful with types - use Data.List.genericLength here instead of length. Otherwise, tm_silly n is wrong for n >= 13 (on my 32-bit machine) due to round-off error in the Int type.
Are you sure you really tested tm_silly ? length is perfectly enough to count the 0 in n! since the number of zeros don't go over the Int limit before n = 8_589_934_615 (though this solution will stack overflow due to the product much sooned than that). -- Jedaï

I wrote:
Be careful with types - use Data.List.genericLength here instead of length. Otherwise, tm_silly n is wrong for n >= 13 (on my 32-bit machine) due to round-off error in the Int type.
Are you sure you really tested tm_silly ? length is perfectly enough to count the 0 in n! since the number of zeros don't go over the Int limit
True, that is not the problem. Using length forces the result to be Int, which is different than all of the other tm's so far. So for example, try this: [n | n <- [0..25], tm_silly n /= tm n] -Yitz

2007/8/26, Yitzchak Gale
True, that is not the problem.
Using length forces the result to be Int, which is different than all of the other tm's so far. So for example, try this:
[n | n <- [0..25], tm_silly n /= tm n]
You mean to say that tm_silly returns Int, which means we can't use it directly in a comparison but have to use toInteger or fromInteger ? Ok, in this case, but it's still a nice test for our more optimized functions (and using genericLength is much slower than toInteger . length, though of course the results differ for really long list) $> [n | n <- [1..1000], toInteger (tm_silly n) /= tm n] [] -- Jedaï

On Fri, 24 Aug 2007, Arie Groeneveld wrote:
I defined several functions for calculating the number of trailing zero's of n!
tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5
This is very elegant! You could also inline 'f' tm4 = sum . takeWhile(>0) . tail . iterate (flip div 5)

tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5
Quite nice. I like tm5 0 = 0 tm5 n = let q = div n 5 in q + tm5 q This version corresponds to what I'm think when parsing |tm|, so I wrote it down directly. Also possible tm6 = sum . unfoldr ( \ n -> case div n 5 of 0 -> mzero q -> return (q,q) ) I tend to not use |iterate|, when it is known in advance, which prefix of the so constructed infinite list is used. /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

On Fri, 24 Aug 2007, Mirko Rahn wrote:
tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5
Quite nice. I like
tm5 0 = 0 tm5 n = let q = div n 5 in q + tm5 q
This version corresponds to what I'm think when parsing |tm|, so I wrote it down directly.
Since the original poster used the message title "style", I want to mention that his solution is good style, because it keeps logical steps separated, and thus lets you inspect meaningful interim results. (iterate f . f) computes the number of natural numbers up to n with factors 5, 5^2, 5^3 and so on. Then you like to sum these up (sum), but before this, you must limit the list to a reasonable finite prefix (takeWhile (>0)). Of course, using 'show' and counting the zeros is more intuitive. It is not efficient, but it will serve as a nice test of 'tm's correctness.

Thanks for all the instructive replies and alternatives! Learned a bit more in terms of feeling about style and improvement of some of the functions: f.e. 'killing' the 'where' in my number one choice. Thanks @@i

Arie Groeneveld wrote:
tm = sum . takeWhile(>0) . iterate f . f where f = flip div 5
Which one is the most elegant one generally speaking?
I like that tm only uses div.
My personal choice is 'tm'. I like 'tm3' (a revised version of tm2) in terms of pointlessness and not having a 'where', but I think it's a bit contrived because of the 'flip'.
You can make tm whereless by noticing that you use because you use the function twice in iterate f . f, which is because you don't want the initial value that iterate gives. You can instead use tail on iterate's result, and use a section to avoid flip: tm = sum . takeWhile (>0) . tail . iterate (`div` 5) (Hope that works, can't test now...) All the best Christian Sievers
participants (8)
-
Arie Groeneveld
-
Bjorn Bringert
-
Chaddaï Fouché
-
Henning Thielemann
-
Marc A. Ziegert
-
Mirko Rahn
-
sievers@math2.nat.tu-bs.de
-
Yitzchak Gale