[Haskell-cafe] Re: Looking for smallest power of 2 >= Integer

ChrisK haskell at list.mightyreason.com
Tue Dec 4 17:55:44 EST 2007


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<r)
> -- This function is good for p == 2^x where x :: Int
> -- and will fail when abs(r) is greater than about 2^(maxBound::Int)
> --
> -- Other policies for r<0 are possible.
> roundUpPower2 :: Integer -> 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<r)
> 
> main = do mapM_ print test
>           print (all check test)
> 



More information about the Haskell-Cafe mailing list