{-# 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 GHC.Prim import Data.Bits(Bits(..)) import Control.Monad(join) import Control.Arrow() import Debug.Trace -- | '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) = {-# SCC "intLog" #-} I# (intLog1 (int2Word# x)) where intLog1 x# = let ans# = uncheckedShiftRL# x# 16# in if ans# `eqWord#` 0## then intLog2 x# else 16# +# intLog2 ans# intLog2 x# = let ans# = uncheckedShiftRL# x# 8# in if ans# `eqWord#` 0## then intLog3 x# else 8# +# intLog3 ans# intLog3 x# = let ans# = uncheckedShiftRL# x# 4# in if ans# `eqWord#` 0## then intLog4 x# else 4# +# intLog4 ans# intLog4 x# = let ans# = uncheckedShiftRL# x# 2# in if ans# `eqWord#` 0## then intLog5 x# else 2# +# intLog5 ans# intLog5 x# = if x# `leWord#` 1## then 0# else 1# {-# INLINE ceilLog #-} -- | 'ceilLog' is equivalent to @ceiling . logBase 2@, but uses heavy bit manipulation to achieve maximum speed. ceilLog :: Int -> Int ceilLog i = intLog (double i - 1) -- | 'floor2Pow' is equivalent to @bit . intLog@. floor2Pow :: Int -> Int floor2Pow = pow2 . intLog isPow2 :: Int -> Bool isPow2 (I# x#) = let w# = int2Word# x#; w'# = w# `minusWord#` 1## in (w# `and#` w'#) `eqWord#` 0## ceil2Pow :: Int -> Int ceil2Pow x | isPow2 x = x | otherwise = floor2Pow (double x) {-# INLINE double #-} -- | 'double' is (unsurprisingly) equivalent to @(2*)@. double :: Int -> Int double (I# i) = I# (i +# i) {-# INLINE half #-} half :: Int -> Int half (I# i) = I# (i `quotInt#` 2#)--(I# i#) = I# (uncheckedIShiftRA# i# 1#) -- | '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 if r ==# 0# then I# m else I# r {-# INLINE quotRem' #-} quotRem' :: Int -> Int -> (Int, Int) I# n `quotRem'` I# m = (I# (n `quotInt#` m), I# (n `remInt#` m))