[Haskell-cafe] How to calculate the number of digits of an integer? (was: Is logBase right?)

Uwe Hollerbach uhollerbach at gmail.com
Sat Aug 29 18:31:25 EDT 2009


Ouch! That is indeed an improvement... I don't recall all the details
of this codelet, but I think I got the seed off the net somewhere
(perhaps this list?), and it might well have been better originally.
So, brightly brightly and with beauty, I probably executed a
verschlimmbesserung. After a year and a half, I find I still have
almost no intuition about performance issues in haskell... guess I
have to practice more.

Uwe

On 8/29/09, Bertram Felgenhauer <bertram.felgenhauer at googlemail.com> wrote:
> Uwe Hollerbach wrote:
>> Here's my version... maybe not as elegant as some, but it seems to
>> work. For base 2 (or 2^k), it's probably possible to make this even
>> more efficient by just walking along the integer as stored in memory,
>> but that difference probably won't show up until at least tens of
>> thousands of digits.
>>
>> Uwe
>>
>> ilogb :: Integer -> Integer -> Integer
>> ilogb b n | n < 0      = ilogb b (- n)
>>           | n < b      = 0
>>           | otherwise  = (up 1) - 1
>>   where up a = if n < (b ^ a)
>>                   then bin (quot a 2) a
>>                   else up (2*a)
>>         bin lo hi = if (hi - lo) <= 1
>>                        then hi
>>                        else let av = quot (lo + hi) 2
>>                             in if n < (b ^ av)
>>                                   then bin lo av
>>                                   else bin av hi
>
> We can streamline this algorithm, avoiding the repeated iterated squaring
> of the base that (^) does:
>
> -- numDigits b n | n < 0 = 1 + numDigits b (-n)
> numDigits b n = 1 + fst (ilog b n) where
>     ilog b n
>         | n < b     = (0, n)
>         | otherwise = let (e, r) = ilog (b*b) n
>                       in  if r < b then (2*e, r) else (2*e+1, r `div` b)
>
> It's a worthwhile optimization, as timings on n = 2^1000000 show:
>
>     Prelude T> length (show n)
>     301030
>     (0.48 secs, 17531388 bytes)
>     Prelude T> numDigits 10 n
>     301030
>     (0.10 secs, 4233728 bytes)
>     Prelude T> ilogb 10 n
>     301029
>     (1.00 secs, 43026552 bytes)
>
> (Code compiled with -O2, but the interpreted version is just as fast; the
> bulk of the time is spent in gmp anyway.)
>
> Regards,
>
> Bertram
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list