{-# LANGUAGE MagicHash #-} -- | 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# (intLog1 (int2Word# x)) where intLog1 x# = let ans# = uncheckedShiftRL# x# 16# in if ans# `eqWord#` 0## then intLog2 0# x# else intLog2 16# ans# intLog2 r# x# = let ans# = uncheckedShiftRL# x# 8# in if ans# `eqWord#` 0## then intLog3 r# x# else intLog3 (r# +# 8#) ans# intLog3 r# x# = let ans# = uncheckedShiftRL# x# 4# in if ans# `eqWord#` 0## then intLog4 r# x# else intLog4 (r# +# 4#) ans# intLog4 r# x# = let ans# = uncheckedShiftRL# x# 2# in if ans# `eqWord#` 0## then intLog5 r# x# else intLog5 (r# +# 2#) ans# intLog5 r# x# = if x# `leWord#` 1## then r# else r# +# 1# -- | 'ceilLog' is equivalent to @ceiling . logBase 2@, but uses heavy bit manipulation to achieve maximum speed. ceilLog :: Int -> Int ceilLog (I# i#) = intLog (I# (i# +# i# -# 1#)) -- | 'floor2Pow' is equivalent to @bit . intLog@. floor2Pow :: Int -> Int floor2Pow = pow2 . intLog -- floor2Pow x = case x .&. (x-1) of -- 0 -> x -- x' -> floor2Pow x' {-# INLINE double #-} -- | 'double' is (unsurprisingly) equivalent to @(2*)@. double :: Int -> Int double (I# i#) = I# (i# +# i#) -- | 'pow2' uses bit shifting to quickly find a power of 2. {-# INLINE pow2 #-} pow2 :: Int -> Int--(Num a, Integral b) => b -> a pow2 (I# i#) = I# (uncheckedIShiftL# 1# i#) --fromIntegral (bit (fromIntegral i) :: Int) {-# INLINE divCeil #-} -- | @a `divCeil` b@ is equivalent to @ceiling (a / b)@, but uses integer division only. divCeil :: Int -> Int -> Int I# a# `divCeil` I# b# = I# ((a# +# b# -# 1#) `quotInt#` b#) {-# INLINE modCeil #-} -- | @a `modCeil` b@ is equivalent to @let m = a `mod` b in if m == 0 then b else m@. modCeil :: Int -> Int -> Int I# n# `modCeil` I# m# = let r# = n# `remInt#` m# in I# (if r# ==# 0# then m# else r#)