{-# LANGUAGE CPP, BangPatterns #-} #if __GLASGOW_HASKELL__ {-# LANGUAGE MagicHash #-} #endif module Data.RangeMin.Common.Math (bit', bitW, div', mod', ceilLog, intLog) where import Data.Bits (Bits(..)) import Data.Word #if __GLASGOW_HASKELL__ -- Unchecked versions of normal arithmetic functions, for when you just need -- the performance that badly. import GHC.Exts import GHC.Base div', mod' :: Int -> Int -> Int bit' :: Int -> Int bitW :: Int -> Word div' = quotInt mod' = remInt bit' (I# i#) = I# (uncheckedIShiftL# 1# i#) bitW (I# i#) = W# (uncheckedShiftL# 1## i#) #else div', mod' :: Int -> Int -> Int bit' :: Int -> Int bitW :: Int -> Word div' = quot mod' = rem bit' = bit bitW = bit #endif ceilLog :: Int -> Int ceilLog n = intLog (2 * n - 1) intLog :: Int -> Int intLog = fromIntegral . wordLog . fromIntegral #include "MachDeps.h" wordLog :: Word -> Word #if WORD_SIZE_IN_BITS == 64 wordLog v = intLog5 v 0 where intLog5 = intLogI 5 intLog4 #elif WORD_SIZE_IN_BITS == 32 wordLog v = intLog4 v 0 where #else wordLog !v = fromIntegral (binSearch 0 (bitSize (0 :: Word))) where binSearch !i !d = case d of 1 -> i 2 -> if bitW (i+1) <= v then i+1 else i _ -> let !d' = d `div'` 2 !m = i + d' !bm = bitW m in if bm <= v then binSearch m (d - d') else binSearch i d' #endif intLog4 = intLogI 4 $ intLogI 3 $ intLogI 2 $ intLogI 1 $ intLogI 0 $ \ _ r -> r {-# INLINE [0] intLogI #-} intLogI !i intLogI' = let bi = bit i !maski = (bit bi - 1) `shiftL` bi in \ !v !r -> case v .&. maski of 0 -> intLogI' v r _ -> intLogI' (v `shiftR` bi) (r .|. fromIntegral bi)