Looking for smallest power of 2 >= Integer

Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve quite a bit of useless copying of data internally by the implementation of Integer. -- Dan

On Dec 3, 2007, at 23:36 , Dan Piponi wrote:
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does
Isn't Integer unlimited (well, limited by RAM)? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Mon, Dec 03, 2007 at 11:40:14PM -0500, Brandon S. Allbery KF8NH wrote:
On Dec 3, 2007, at 23:36 , Dan Piponi wrote:
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does
Isn't Integer unlimited (well, limited by RAM)?
Any *specific* integer has a finite number of 1-bits. Stefan

dpiponi:
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve quite a bit of useless copying of data internally by the implementation of Integer.
Well, you could use testBit, which is pretty efficient, x `testBit` i = (x .&. bit i) /= 0 (J# s1 d1) .&. (J# s2 d2) = case andInteger# s1 d1 s2 d2 of (# s, d #) -> J# s d Of course, working out which bit to test is the puzzle :) Just for fun, I tried to see how large gmp could go, import Data.Bits import Text.Printf main = mapM_ test [0,100000000 ..] where test n = printf "2 ^ %d has bit %d set: %s\n" n n (show t) where t = (2 ^ n :: Integer) `testBit` n gmp is quite remarkable. $ ghc -O2 A.hs -o A $ time ./A 2 ^ 0 has bit 0 set: True 2 ^ 100000000 has bit 100000000 set: True 2 ^ 200000000 has bit 200000000 set: True 2 ^ 300000000 has bit 300000000 set: True 2 ^ 400000000 has bit 400000000 set: True 2 ^ 500000000 has bit 500000000 set: True 2 ^ 600000000 has bit 600000000 set: True A: out of memory (requested 202375168 bytes) ./A 504.00s user 1.73s system 99% cpu 8:26.71 total and I ran out of ram. -- Don

On Dec 3, 2007 9:10 PM, Don Stewart
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? Well, you could use testBit, which is pretty efficient,
But testBit tests only one bit at a time. To prove that i is the highest bit of n I need to prove that all higher bits are set to zero, and I can't do that with testBit. The obvious thing is "shiftR n i == 0" but I'm worried that that entails the wasteful operation of shifting all of the bits above bit i. Internally the implementation of Integer must know a good upper bound on where the highest bit is. Maybe I need to delve into GHC.Prim. -- Dan

dpiponi:
On Dec 3, 2007 9:10 PM, Don Stewart
wrote: Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? Well, you could use testBit, which is pretty efficient,
But testBit tests only one bit at a time. To prove that i is the highest bit of n I need to prove that all higher bits are set to zero, and I can't do that with testBit. The obvious thing is "shiftR n i == 0" but I'm worried that that entails the wasteful operation of shifting all of the bits above bit i. Internally the implementation of Integer must know a good upper bound on where the highest bit is. Maybe I need to delve into GHC.Prim.
Yes, perhaps look into what GMP provides, then bind to it, and call it on the underlying ByteArray# -- Don

Actually, I suspect GHC's strictness analyzer will give you reasonable performance with even the naive version, but fancier ideas are at http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog The problem with all those, however, is since they do bit-twiddling and use shifts and masks, they're designed to, as far as I can tell, only work on integers of defined sizes (the names given to the functions to the contrary). You could, of course, dynamically choose how many masks to apply based on the length of the Integer in question, which can, if all else fails, be determined by unpacking it into the primitives, which are (# Int#, ByteArr# #) with the Int# as the number of "limbs" of the integer, as well as its sign. As far as I understand it, each "limb" is generally 32 bits. Unless this is a real performance hotspot, you're probably fine sticking with a relatively naive version. For example, in my translation of the clean version of the meteor-contest shootout entry, I used the following function (which, I'll grant, does something slightly different): first0 :: Mask -> Int first0 i | i .&. 1 == 0 = 0 | otherwise = 1 + first0 (i `shiftR` 1) and it worked out fine for my purposes. --s. On Dec 3, 2007, at 11:36 PM, Dan Piponi wrote:
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve quite a bit of useless copying of data internally by the implementation of Integer. -- Dan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12/3/07, Dan Piponi
On Dec 3, 2007 9:32 PM, Sterling Clover
wrote: if all else fails, be determined by unpacking it into the primitives, which are (# Int#, ByteArr# #) with the Int# as the number of "limbs" of the integer, as well as its sign.
That's the answer I'm looking for, thanks.
Could you please post your code here when you're done? I'd be interested to see the final result.

Sterling Clover wrote:
Actually, I suspect GHC's strictness analyzer will give you reasonable performance with even the naive version, but fancier ideas are at http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog
If given an 'n' you are looking for the (2^x) such that 2^x >= n > 2^(x-1) then you could use the method at http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2 This does not return 'x', it returns the integer '2^x' instead. Here is my contribution:
import Data.Bits
-- Takes input Integer >=0 -- let p = roundUpPower2 r -- in assert ( ((r==0) && (p==1)) -- || (r>0) && (p>=r) && (p<2*r) -- || (r<0) && (p>=r) && (2*p
Integer roundUpPower2 r = case compare r 0 of LT -> let p' = negate (roundUpPower2 (negate r)) in if p' == r then p' else p' `div` 2 EQ -> 1 GT -> shifting (pred r) 1 where shifting !v !k | sv == 0 = succ v | otherwise = shifting (v .|. sv) (shiftL k 1) where sv = shiftR v k test = map (\r -> (r,roundUpPower2 r)) [-17..17]
check (r,p) = ((r==0) && (p==1)) || (r>0) && (p>=r) && (p<2*r) || (r<0) && (p>=r) && (2*p
main = do mapM_ print test print (all check test)

Dan Piponi wrote:
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve quite a bit of useless copying of data internally by the implementation of Integer. -- Dan The subject line and your description disagree by 1 bit. Take the number 7: its binary representation would be 0111, with 0100 being the highest bit, whereas the smallest power of 2 >= 7 is 8, or 1000 in binary. And how do you want the results? The place value of that highest bit? Or its index?
For the index, how about this: truncate . (/(log 2)) . log . fromIntegral for the place value, just add an exponent function and another cast: (2**) . fromIntegral . truncate . (/(log 2)) . log . fromIntegral If you want the smallest power of 2 >= the integer, just change truncate to ceiling.

Whatever the answer is, I expect it's relevant to Data.IntSet, which uses
big-endian patricia trees. - Conal
On Dec 3, 2007 8:36 PM, Dan Piponi
Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve quite a bit of useless copying of data internally by the implementation of Integer. -- Dan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (9)
-
Brandon S. Allbery KF8NH
-
ChrisK
-
Conal Elliott
-
Dan Piponi
-
David Benbennick
-
Don Stewart
-
Stefan O'Rear
-
Sterling Clover
-
Steven Fodstad