module Feldspar.Core.Frontend.Bits
where
import Prelude hiding (Integral(..))
import Data.Int
import Data.Word
import Feldspar.Range (Range(..))
import Feldspar.Core.Types
import Feldspar.Core.Constructs
import Feldspar.Core.Constructs.Bits
import Feldspar.Core.Frontend.Integral
import Feldspar.Core.Frontend.Literal
import qualified Data.Bits as B
infixl 5 .<<.,.>>.
infixl 4 ⊕
class (Type a, B.Bits a, Integral a, Bounded a, Size a ~ Range a) => Bits a
where
(.&.) :: Data a -> Data a -> Data a
(.&.) = sugarSymF BAnd
(.|.) :: Data a -> Data a -> Data a
(.|.) = sugarSymF BOr
xor :: Data a -> Data a -> Data a
xor = sugarSymF BXor
complement :: Data a -> Data a
complement = sugarSymF Complement
bit :: Data Index -> Data a
bit = sugarSymF Bit
setBit :: Data a -> Data Index -> Data a
setBit = sugarSymF SetBit
clearBit :: Data a -> Data Index -> Data a
clearBit = sugarSymF ClearBit
complementBit :: Data a -> Data Index -> Data a
complementBit = sugarSymF ComplementBit
testBit :: Data a -> Data Index -> Data Bool
testBit = sugarSymF TestBit
shiftLU :: Data a -> Data Index -> Data a
shiftLU = sugarSymF ShiftLU
shiftRU :: Data a -> Data Index -> Data a
shiftRU = sugarSymF ShiftRU
shiftL :: Data a -> Data IntN -> Data a
shiftL = sugarSymF ShiftL
shiftR :: Data a -> Data IntN -> Data a
shiftR = sugarSymF ShiftR
rotateLU :: Data a -> Data Index -> Data a
rotateLU = sugarSymF RotateLU
rotateRU :: Data a -> Data Index -> Data a
rotateRU = sugarSymF RotateRU
rotateL :: Data a -> Data IntN -> Data a
rotateL = sugarSymF RotateL
rotateR :: Data a -> Data IntN -> Data a
rotateR = sugarSymF RotateR
reverseBits :: Data a -> Data a
reverseBits = sugarSymF ReverseBits
bitScan :: Data a -> Data Index
bitScan = sugarSymF BitScan
bitCount :: Data a -> Data Index
bitCount = sugarSymF BitCount
bitSize :: Data a -> Data Index
bitSize = value . bitSize'
bitSize' :: Data a -> Index
bitSize' = const $ fromIntegral $ finiteBitSize (undefined :: a)
isSigned :: Data a -> Data Bool
isSigned = value . isSigned'
isSigned' :: Data a -> Bool
isSigned' = const $ B.isSigned (undefined :: a)
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
finiteBitSize :: (B.FiniteBits b) => b -> Int
finiteBitSize = B.finiteBitSize
#else
finiteBitSize :: (B.Bits b) => b -> Int
finiteBitSize = B.bitSize
#endif
instance Bits Word8
instance Bits Word16
instance Bits Word32
instance Bits Word64
instance Bits WordN
instance Bits Int8
instance Bits Int16
instance Bits Int32
instance Bits Int64
instance Bits IntN
(⊕) :: (Bits a) => Data a -> Data a -> Data a
(⊕) = xor
(.<<.) :: (Bits a) => Data a -> Data Index -> Data a
(.<<.) = shiftLU
(.>>.) :: (Bits a) => Data a -> Data Index -> Data a
(.>>.) = shiftRU
allOnes :: Bits a => Data a
allOnes = complement 0
oneBits :: Bits a => Data Index -> Data a
oneBits n = complement (allOnes .<<. n)
lsbs :: Bits a => Data Index -> Data a -> Data a
lsbs k i = i .&. oneBits k