{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
module Data.Bit.Utils
( modWordSize
, divWordSize
, mulWordSize
, wordSize
, wordsToBytes
, nWords
, aligned
, alignUp
, selectWord
, reverseWord
, reversePartialWord
, masked
, meld
, ffs
, loMask
, hiMask
) where
#include "MachDeps.h"
import Data.Bits
wordSize :: Int
wordSize = finiteBitSize (0 :: Word)
lgWordSize, wordSizeMask, wordSizeMaskC :: Int
lgWordSize = case wordSize of
32 -> 5
64 -> 6
_ -> error "wordsToBytes: unknown architecture"
wordSizeMask = wordSize - 1
wordSizeMaskC = complement wordSizeMask
divWordSize :: Bits a => a -> a
divWordSize x = unsafeShiftR x lgWordSize
{-# INLINE divWordSize #-}
modWordSize :: Int -> Int
modWordSize x = x .&. (wordSize - 1)
{-# INLINE modWordSize #-}
mulWordSize :: Bits a => a -> a
mulWordSize x = unsafeShiftL x lgWordSize
nWords :: Int -> Int
nWords ns = divWordSize (ns + wordSize - 1)
wordsToBytes :: Int -> Int
wordsToBytes ns = case wordSize of
32 -> ns `unsafeShiftL` 2
64 -> ns `unsafeShiftL` 3
_ -> error "wordsToBytes: unknown architecture"
aligned :: Int -> Bool
aligned x = x .&. wordSizeMask == 0
alignUp :: Int -> Int
alignUp x | x == x' = x'
| otherwise = x' + wordSize
where x' = alignDown x
alignDown :: Int -> Int
alignDown x = x .&. wordSizeMaskC
mask :: Int -> Word
mask b = m
where
m | b >= finiteBitSize m = complement 0
| b < 0 = 0
| otherwise = bit b - 1
masked :: Int -> Word -> Word
masked b x = x .&. mask b
meld :: Int -> Word -> Word -> Word
meld b lo hi = (lo .&. m) .|. (hi .&. complement m) where m = mask b
{-# INLINE meld #-}
#if WORD_SIZE_IN_BITS == 64
reverseWord :: Word -> Word
reverseWord x0 = x6
where
x1 = ((x0 .&. 0x5555555555555555) `shiftL` 1) .|. ((x0 .&. 0xAAAAAAAAAAAAAAAA) `shiftR` 1)
x2 = ((x1 .&. 0x3333333333333333) `shiftL` 2) .|. ((x1 .&. 0xCCCCCCCCCCCCCCCC) `shiftR` 2)
x3 = ((x2 .&. 0x0F0F0F0F0F0F0F0F) `shiftL` 4) .|. ((x2 .&. 0xF0F0F0F0F0F0F0F0) `shiftR` 4)
x4 = ((x3 .&. 0x00FF00FF00FF00FF) `shiftL` 8) .|. ((x3 .&. 0xFF00FF00FF00FF00) `shiftR` 8)
x5 = ((x4 .&. 0x0000FFFF0000FFFF) `shiftL` 16) .|. ((x4 .&. 0xFFFF0000FFFF0000) `shiftR` 16)
x6 = ((x5 .&. 0x00000000FFFFFFFF) `shiftL` 32) .|. ((x5 .&. 0xFFFFFFFF00000000) `shiftR` 32)
#else
reverseWord :: Word -> Word
reverseWord x0 = x5
where
x1 = ((x0 .&. 0x5555555555555555) `shiftL` 1) .|. ((x0 .&. 0xAAAAAAAAAAAAAAAA) `shiftR` 1)
x2 = ((x1 .&. 0x3333333333333333) `shiftL` 2) .|. ((x1 .&. 0xCCCCCCCCCCCCCCCC) `shiftR` 2)
x3 = ((x2 .&. 0x0F0F0F0F0F0F0F0F) `shiftL` 4) .|. ((x2 .&. 0xF0F0F0F0F0F0F0F0) `shiftR` 4)
x4 = ((x3 .&. 0x00FF00FF00FF00FF) `shiftL` 8) .|. ((x3 .&. 0xFF00FF00FF00FF00) `shiftR` 8)
x5 = ((x4 .&. 0x0000FFFF0000FFFF) `shiftL` 16) .|. ((x4 .&. 0xFFFF0000FFFF0000) `shiftR` 16)
#endif
reversePartialWord :: Int -> Word -> Word
reversePartialWord n w | n >= wordSize = reverseWord w
| otherwise = reverseWord w `shiftR` (wordSize - n)
ffs :: Word -> Maybe Int
ffs 0 = Nothing
ffs x = Just $! (popCount (x `xor` complement (-x)) - 1)
{-# INLINE ffs #-}
selectWord :: Word -> Word -> (Int, Word)
selectWord m x = loop 0 0 0
where
loop !i !ct !y
| i >= wordSize = (ct, y)
| testBit m i = loop (i + 1)
(ct + 1)
(if testBit x i then setBit y ct else y)
| otherwise = loop (i + 1) ct y
loMask :: Int -> Word
loMask n = 1 `shiftL` n - 1
hiMask :: Int -> Word
hiMask n = complement (1 `shiftL` n - 1)