How to calculate de number of digits of an integer? (was: Is logBase right?)

Ok. I wonder if someone could help me with this problem... I want to calculate the number of digits of a positive integer. I was thinking of ... numDigits n = truncate (logBase 10 n) + 1 But (logBase 10 1000) = 2.9999999999999996 so numDigits 1000 = 2. Maybe adding a small amount numDigits n = truncate ((logBase 10 n) + 0.0000000000000005) + 1 Prelude> numDigits 100 3 Prelude> numDigits 1000 4 Prelude> numDigits 10000 5 Prelude> numDigits 10000 5 Prelude> numDigits 100000 6 Prelude> numDigits 1000000 7 Prelude> numDigits 10000000 8 Prelude> numDigits 100000000 9 Prelude> numDigits 1000000000 9 <---- This is wrong!!!! Prelude> numDigits 10000000000 11 Is there a reliable way to calculate the number of digits by means of logBase? Regards!

Use 'round' instead of 'truncate'.
Prelude> let numDigits = (+1) . round . logBase 10 . fromIntegral
Prelude> map (numDigits . (10^)) [0..9]
[1,2,3,4,5,6,7,8,9,10]
2009/8/22 Roberto López
Ok. I wonder if someone could help me with this problem...
I want to calculate the number of digits of a positive integer. I was thinking of ...
numDigits n = truncate (logBase 10 n) + 1
But (logBase 10 1000) = 2.9999999999999996 so numDigits 1000 = 2.
Maybe adding a small amount
numDigits n = truncate ((logBase 10 n) + 0.0000000000000005) + 1
Prelude> numDigits 100 3 Prelude> numDigits 1000 4 Prelude> numDigits 10000 5 Prelude> numDigits 10000 5 Prelude> numDigits 100000 6 Prelude> numDigits 1000000 7 Prelude> numDigits 10000000 8 Prelude> numDigits 100000000 9 Prelude> numDigits 1000000000 9 <---- This is wrong!!!! Prelude> numDigits 10000000000 11
Is there a reliable way to calculate the number of digits by means of logBase?
Regards!
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Or better numDigits = length . show
It's probably even faster.
2009/8/22 Eugene Kirpichov
Use 'round' instead of 'truncate'.
Prelude> let numDigits = (+1) . round . logBase 10 . fromIntegral Prelude> map (numDigits . (10^)) [0..9] [1,2,3,4,5,6,7,8,9,10]
2009/8/22 Roberto López
: Ok. I wonder if someone could help me with this problem...
I want to calculate the number of digits of a positive integer. I was thinking of ...
numDigits n = truncate (logBase 10 n) + 1
But (logBase 10 1000) = 2.9999999999999996 so numDigits 1000 = 2.
Maybe adding a small amount
numDigits n = truncate ((logBase 10 n) + 0.0000000000000005) + 1
Prelude> numDigits 100 3 Prelude> numDigits 1000 4 Prelude> numDigits 10000 5 Prelude> numDigits 10000 5 Prelude> numDigits 100000 6 Prelude> numDigits 1000000 7 Prelude> numDigits 10000000 8 Prelude> numDigits 100000000 9 Prelude> numDigits 1000000000 9 <---- This is wrong!!!! Prelude> numDigits 10000000000 11
Is there a reliable way to calculate the number of digits by means of logBase?
Regards!
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru
-- Eugene Kirpichov Web IR developer, market.yandex.ru

2009/8/22 Eugene Kirpichov
Use 'round' instead of 'truncate'.
Prelude> let numDigits = (+1) . round . logBase 10 . fromIntegral Prelude> map (numDigits . (10^)) [0..9] [1,2,3,4,5,6,7,8,9,10]
round won't work because 999 is close to 1000. You simply need to use logBase 10 as a guess and then check the answer, e.g. numDigits n | n < n' = e | otherwise = e + 1 where e = ceiling $ logBase 10 $ fromIntegral n n' = 10^e This will need to special case 0 which it currently doesn't do.

On Sat, Aug 22, 2009 at 12:31 PM, Derek Elkins
2009/8/22 Eugene Kirpichov
: Use 'round' instead of 'truncate'.
Prelude> let numDigits = (+1) . round . logBase 10 . fromIntegral Prelude> map (numDigits . (10^)) [0..9] [1,2,3,4,5,6,7,8,9,10]
round won't work because 999 is close to 1000.
You simply need to use logBase 10 as a guess and then check the answer, e.g. numDigits n | n < n' = e | otherwise = e + 1 where e = ceiling $ logBase 10 $ fromIntegral n n' = 10^e This will need to special case 0 which it currently doesn't do.
Note that logBase 10 will start failing for large Integers (or rather fromIntegral will.) Writing an integer log using a binary search would be relatively easy, reasonably efficient, and would work for all Integers.

Ouch, my bad. length.show is better :)
2009/8/22 Derek Elkins
2009/8/22 Eugene Kirpichov
: Use 'round' instead of 'truncate'.
Prelude> let numDigits = (+1) . round . logBase 10 . fromIntegral Prelude> map (numDigits . (10^)) [0..9] [1,2,3,4,5,6,7,8,9,10]
round won't work because 999 is close to 1000.
You simply need to use logBase 10 as a guess and then check the answer, e.g. numDigits n | n < n' = e | otherwise = e + 1 where e = ceiling $ logBase 10 $ fromIntegral n n' = 10^e This will need to special case 0 which it currently doesn't do.
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Hello Roberto, Saturday, August 22, 2009, 9:19:26 PM, you wrote:
I want to calculate the number of digits of a positive integer. I was
fastest way digits = iterate (`div` 10) >>> takeWhile (>0) >>> length -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

It looks like length . show is faster Prelude Control.Arrow> let numDigits n = length $ show n Prelude Control.Arrow> let digits = iterate (`div` 10) >>> takeWhile (>0)
length Prelude Control.Arrow> let n=2^1000000 Prelude Control.Arrow> :set +s Prelude Control.Arrow> numDigits n 301030 (0.39 secs, 23001616 bytes) Prelude Control.Arrow> digits n 301030 (51.06 secs, 19635437248 bytes)
2009/8/22 Bulat Ziganshin
Hello Roberto,
Saturday, August 22, 2009, 9:19:26 PM, you wrote:
I want to calculate the number of digits of a positive integer. I was
fastest way
digits = iterate (`div` 10) >>> takeWhile (>0) >>> length
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, 22 Aug 2009, Bulat Ziganshin wrote:
Hello Roberto,
Saturday, August 22, 2009, 9:19:26 PM, you wrote:
I want to calculate the number of digits of a positive integer. I was
fastest way
digits = iterate (`div` 10) >>> takeWhile (>0) >>> length
This needs quadratic time with respect to the number of digits, doesn't it? If (show . length) is not fast enough, I would try to catch the magnitude by repeated squaring of 10. If you have found a 'k' with 10^(2^k) <= n < 10^(2^(k+1)) then you can start to find the exact number of digits with bisection.

Hello Henning, Tuesday, August 25, 2009, 6:11:00 PM, you wrote:
digits = iterate (`div` 10) >>> takeWhile (>0) >>> length
This needs quadratic time with respect to the number of digits, doesn't it?
why? i think that `show` uses pretty the same way to build list of digits, so we just omit unneeded computations -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin schrieb:
Hello Henning,
Tuesday, August 25, 2009, 6:11:00 PM, you wrote:
digits = iterate (`div` 10) >>> takeWhile (>0) >>> length
This needs quadratic time with respect to the number of digits, doesn't it?
why?
Because division by 10 needs linear time.
i think that `show` uses pretty the same way to build list of digits, so we just omit unneeded computations
I hope that 'show' will not need quadratic time but will employ a more efficient algorithm that is certainly implemented in the GNU multiprecision library. I assume that a division by 10^(2^k) will require about 2^k * k operations. At least, it should be considerably faster than repeatedly dividing by 10.

You could also fudge the input: {-# LANGUAGE NoMonomorphismRestriction #-} log10 = floor . logBase 10 . (0.5+) . fromIntegral numDigits n | n < 0 = 1 + numDigits (-n) numDigits 0 = 1 numDigits n = 1 + log10 n -- checked [0..10^8], finding a counter-example is left as an exercise :P

Am Mittwoch 26 August 2009 06:29:47 schrieb George Pollard:
You could also fudge the input:
{-# LANGUAGE NoMonomorphismRestriction #-}
log10 = floor . logBase 10 . (0.5+) . fromIntegral
numDigits n | n < 0 = 1 + numDigits (-n) numDigits 0 = 1 numDigits n = 1 + log10 n
-- checked [0..10^8], finding a counter-example is left as an exercise :P
Prelude> numDigits (10^15) 15

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 numDigits n = 1 + ilogb 10 n [fire up ghci, load, etc] *Main> numDigits (10^1500 - 1) 1500 *Main> numDigits (10^1500) 1501

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

I have a version of this inside of the monoid library buried in the
Data.Ring.Semi.BitSet module:
http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-...
http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-...To
do any better by walking the raw Integer internals you need to know the
'finger' size for the GMP for your platform, which isn't possible to do
portably.
-Edward Kmett
On Wed, Aug 26, 2009 at 10:42 AM, Uwe Hollerbach
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
numDigits n = 1 + ilogb 10 n
[fire up ghci, load, etc]
*Main> numDigits (10^1500 - 1) 1500 *Main> numDigits (10^1500) 1501 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Although this isn't a very "general approach", I just submitted a
patch to GHC (not yet merged) with a gmp binding to mpz_sizeinbase,
which would allow for very quick computation of number of digits in
any base.
On Sat, Aug 29, 2009 at 9:12 PM, Edward Kmett
I have a version of this inside of the monoid library buried in the Data.Ring.Semi.BitSet module: http://comonad.com/haskell/monoids/dist/doc/html/monoids/src/Data-Ring-Semi-... To do any better by walking the raw Integer internals you need to know the 'finger' size for the GMP for your platform, which isn't possible to do portably. -Edward Kmett
On Wed, Aug 26, 2009 at 10:42 AM, 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
numDigits n = 1 + ilogb 10 n
[fire up ghci, load, etc]
*Main> numDigits (10^1500 - 1) 1500 *Main> numDigits (10^1500) 1501 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (13)
-
Bertram Felgenhauer
-
Bulat Ziganshin
-
Daniel Fischer
-
Daniel Peebles
-
Derek Elkins
-
Edward Kmett
-
Eugene Kirpichov
-
George Pollard
-
Henning Thielemann
-
Henning Thielemann
-
José Prous
-
Roberto López
-
Uwe Hollerbach