{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Capnp.Bits
( BitCount(..)
, ByteCount(..)
, WordCount(..)
, Word1(..)
, bitsToBytesCeil
, bytesToWordsCeil
, bytesToWordsFloor
, wordsToBytes
, lo, hi
, i32, i30, i29
, fromLo, fromHi
, fromI32, fromI30, fromI29
, bitRange
, replaceBits
)
where
import Data.Bits
import Data.Int
import Data.Word
newtype BitCount = BitCount Int
deriving(Num, Real, Integral, Bits, Ord, Eq, Enum, Show)
newtype ByteCount = ByteCount Int
deriving(Num, Real, Integral, Bits, Ord, Eq, Enum, Show)
newtype WordCount = WordCount Int
deriving(Num, Real, Integral, Bits, Ord, Eq, Enum, Show)
bitsToBytesCeil :: BitCount -> ByteCount
bitsToBytesCeil (BitCount n) = ByteCount ((n + 7) `div` 8)
bytesToWordsCeil :: ByteCount -> WordCount
bytesToWordsCeil (ByteCount n) = WordCount ((n + 7) `div` 8)
bytesToWordsFloor :: ByteCount -> WordCount
bytesToWordsFloor (ByteCount n) = WordCount (n `div` 8)
wordsToBytes :: WordCount -> ByteCount
wordsToBytes (WordCount n) = ByteCount (n * 8)
lo, hi :: Word64 -> Word32
i32, i30, i29 :: Word32 -> Int32
fromLo, fromHi :: Word32 -> Word64
fromI32, fromI30, fromI29 :: Int32 -> Word32
lo w = fromIntegral (w `shiftR` 0)
hi w = fromIntegral (w `shiftR` 32)
i32 = fromIntegral
i30 w = i32 w `shiftR` 2
i29 w = i32 w `shiftR` 3
fromLo w = fromIntegral w `shiftL` 0
fromHi w = fromIntegral w `shiftL` 32
fromI32 = fromIntegral
fromI30 w = fromI32 (w `shiftL` 2)
fromI29 w = fromI32 (w `shiftL` 3)
bitRange :: (Integral a => Word64 -> Int -> Int -> a)
bitRange word lo hi = fromIntegral $
(word .&. ((1 `shiftL` hi) - 1)) `shiftR` lo
replaceBits :: (Bounded a, Integral a)
=> a -> Word64 -> Int -> Word64
replaceBits new orig shift =
(orig .&. mask) .|. (fromIntegral new `shiftL` shift)
where
mask = complement $ fromIntegral (maxBound `asTypeOf` new) `shiftL` shift
newtype Word1 = Word1 { word1ToBool :: Bool }
deriving(Ord, Eq, Enum, Bounded, Bits)
instance Num Word1 where
(+) = w1ThruEnum (+)
(*) = w1ThruEnum (*)
abs = id
signum = id
negate = id
fromInteger x = toEnum (fromIntegral x `mod` 2)
instance Real Word1 where
toRational = fromIntegral . fromEnum
instance Integral Word1 where
toInteger = toInteger . fromEnum
quotRem x y = let (x', y') = quotRem (fromEnum x) (fromEnum y)
in (toEnum x', toEnum y')
instance Show Word1 where
show = show . fromEnum
w1ThruEnum :: (Int -> Int -> Int) -> Word1 -> Word1 -> Word1
w1ThruEnum op l r = toEnum $ (fromEnum l `op` fromEnum r) `mod` 2