{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module Haskus.Binary.Bits.Index
( IndexableBits (..)
)
where
import Haskus.Binary.Bits.Shift
import Haskus.Binary.Bits.Bitwise
import Haskus.Binary.Bits.Finite
import Haskus.Number.Word
import Haskus.Number.Int
import GHC.Exts
import qualified Data.Bits as BaseBits
import Numeric.Natural
class IndexableBits a where
bit :: Word -> a
default bit :: (Num a, ShiftableBits a) => Word -> a
bit i = 1 `shiftL` i
setBit :: a -> Word -> a
default setBit :: (Bitwise a) => a -> Word -> a
setBit a i = a .|. bit i
clearBit :: a -> Word -> a
default clearBit :: (FiniteBits a,Bitwise a) => a -> Word -> a
clearBit a i = a .&. complement (bit i)
complementBit :: a -> Word -> a
default complementBit :: (Bitwise a) => a -> Word -> a
complementBit a i = a `xor` bit i
testBit :: a -> Word -> Bool
default testBit :: (Bitwise a, Num a, Eq a) => a -> Word -> Bool
testBit a i = (a .&. bit i) /= 0
popCount :: a -> Word
default popCount :: (Bitwise a, Num a, Eq a) => a -> Word
popCount = go 0
where
go !c 0 = c
go c w = go (c+1) (w .&. (w-1))
instance IndexableBits Word where
popCount (W# x#) = W# (popCnt# x#)
instance IndexableBits Word8 where
popCount (W8# x#) = W# (popCnt8# x#)
instance IndexableBits Word16 where
popCount (W16# x#) = W# (popCnt16# x#)
instance IndexableBits Word32 where
popCount (W32# x#) = W# (popCnt32# x#)
instance IndexableBits Word64 where
popCount (W64# x#) = W# (popCnt64# x#)
instance IndexableBits Int where
popCount (I# x#) = W# (popCnt# (int2Word# x#))
instance IndexableBits Int8 where
popCount (I8# x#) = W# (popCnt8# (int2Word# x#))
instance IndexableBits Int16 where
popCount (I16# x#) = W# (popCnt16# (int2Word# x#))
instance IndexableBits Int32 where
popCount (I32# x#) = W# (popCnt32# (int2Word# x#))
instance IndexableBits Int64 where
popCount (I64# x#) = W# (popCnt64# (int2Word# x#))
instance IndexableBits Integer where
testBit x i = BaseBits.testBit x (fromIntegral i)
bit i = BaseBits.bit (fromIntegral i)
popCount x = fromIntegral (BaseBits.popCount x)
clearBit x i = BaseBits.clearBit x (fromIntegral i)
instance IndexableBits Natural where
testBit x i = BaseBits.testBit x (fromIntegral i)
bit i = BaseBits.bit (fromIntegral i)
popCount x = fromIntegral (BaseBits.popCount x)
clearBit x i = BaseBits.clearBit x (fromIntegral i)