{-# OPTIONS_GHC -XMagicHash #-} -- | A number of useful numeric functions on integer types, primarily emphasizing bit manipulation. -- This module assumes that 'Int' has 32-bit precision. module Data.RangeMin.Internal.HandyNumeric where import GHC.Exts import Data.Bits(Bits(..)) import Control.Monad(join) import Control.Arrow() -- | 'intLog' is equivalent to @floor . logBase 2@, but uses heavy bit manipulation to achieve maximum speed. intLog :: Int -> Int intLog 0 = 0 intLog 1 = 0 intLog (I# x) = I# (word2Int# (intLog1 (int2Word# x))) where zeroq :: Word# -> Bool zeroq x = x `eqWord#` (int2Word# 0#) intLog1 :: Word# -> Word# intLog1 x = let ans = uncheckedShiftRL# x 16# in if zeroq ans then intLog2 x else int2Word# 16# `or#` intLog2 ans intLog2 :: Word# -> Word# intLog2 x = let ans = uncheckedShiftRL# x 8# in if zeroq ans then intLog3 x else int2Word# 8# `or#` intLog3 ans intLog3 :: Word# -> Word# intLog3 x = let ans = uncheckedShiftRL# x 4# in if zeroq ans then intLog4 x else int2Word# 4# `or#` intLog4 ans intLog4 :: Word# -> Word# intLog4 x = let ans = uncheckedShiftRL# x 2# in if zeroq ans then intLog5 x else int2Word# 2# `or#` intLog5 ans intLog5 :: Word# -> Word# intLog5 x = if x `leWord#` int2Word# 1# then int2Word# 0# else int2Word# 1# -- | 'ceilLog' is equivalent to @ceiling . logBase 2@, but uses heavy bit manipulation to achieve maximum speed. ceilLog :: Int -> Int ceilLog = intLog . subtract 1 . double -- | 'floor2Pow' is equivalent to @bit . intLog@. floor2Pow :: Int -> Int floor2Pow = bit . intLog -- floor2Pow x = case x .&. (x-1) of -- 0 -> x -- x' -> floor2Pow x' {-# INLINE double #-} -- | 'double' is (unsurprisingly) equivalent to @(2*)@. double :: Num a => a -> a double = join (+) -- | 'pow2' uses bit shifting to quickly find a power of 2. pow2 :: (Num a, Integral b) => b -> a pow2 i = fromIntegral (bit (fromIntegral i) :: Int) {-# INLINE divCeil #-} -- | @a `divCeil` b@ is equivalent to @ceiling (a / b)@, but uses integer division only. divCeil :: Integral a => a -> a -> a divCeil a b = (a + b - 1) `div` b {-# INLINE modCeil #-} -- | @a `modCeil` b@ is equivalent to @let m = a `mod` b in if m == 0 then b else m@. modCeil :: Integral a => a -> a -> a n `modCeil` m = case n `mod` m of 0 -> m r -> r