Copyright | [2016..2020] The Accelerate Team |
---|---|
License | BSD3 |
Maintainer | Trevor L. McDonell <trevor.mcdonell@gmail.com> |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Bitwise operations for signed and unsigned integer expressions.
Synopsis
- class Eq a => Bits a where
- (.&.) :: Exp a -> Exp a -> Exp a
- (.|.) :: Exp a -> Exp a -> Exp a
- xor :: Exp a -> Exp a -> Exp a
- complement :: Exp a -> Exp a
- shift :: Exp a -> Exp Int -> Exp a
- rotate :: Exp a -> Exp Int -> Exp a
- zeroBits :: Exp a
- bit :: Exp Int -> Exp a
- setBit :: Exp a -> Exp Int -> Exp a
- clearBit :: Exp a -> Exp Int -> Exp a
- complementBit :: Exp a -> Exp Int -> Exp a
- testBit :: Exp a -> Exp Int -> Exp Bool
- isSigned :: Exp a -> Exp Bool
- shiftL :: Exp a -> Exp Int -> Exp a
- unsafeShiftL :: Exp a -> Exp Int -> Exp a
- shiftR :: Exp a -> Exp Int -> Exp a
- unsafeShiftR :: Exp a -> Exp Int -> Exp a
- rotateL :: Exp a -> Exp Int -> Exp a
- rotateR :: Exp a -> Exp Int -> Exp a
- popCount :: Exp a -> Exp Int
- class Bits b => FiniteBits b where
- finiteBitSize :: Exp b -> Exp Int
- countLeadingZeros :: Exp b -> Exp Int
- countTrailingZeros :: Exp b -> Exp Int
Documentation
class Eq a => Bits a where Source #
The Bits
class defines bitwise operations over integral scalar expression
types. As usual, bits are numbered from zero, with zero being the least
significant bit.
(.&.), (.|.), xor, complement, (shift | shiftL, shiftR), (rotate | rotateL, rotateR), isSigned, testBit, bit, popCount
(.&.) :: Exp a -> Exp a -> Exp a infixl 7 Source #
Bitwise "and"
(.|.) :: Exp a -> Exp a -> Exp a infixl 5 Source #
Bitwise "or"
xor :: Exp a -> Exp a -> Exp a infixl 6 Source #
Bitwise "xor"
complement :: Exp a -> Exp a Source #
Reverse all bits in the argument
shift :: Exp a -> Exp Int -> Exp a infixl 8 Source #
shifts shift
x ix
left by i
bits if i
is positive, or right by
-i
bits otherwise. Right shifts perform sign extension on signed number
types; i.e. they fill the top bits with 1 if the x
is negative and with
0 otherwise.
rotate :: Exp a -> Exp Int -> Exp a infixl 8 Source #
rotates rotate
x ix
left by i
bits if i
is positive, or right
by -i
bits otherwise.
The value with all bits unset
bit :: Exp Int -> Exp a Source #
bit i
is a value with the i
th bit set and all other bits clear.
setBit :: Exp a -> Exp Int -> Exp a Source #
x `setBit` i
is the same as x .|. bit i
clearBit :: Exp a -> Exp Int -> Exp a Source #
x `clearBit` i
is the same as x .&. complement (bit i)
complementBit :: Exp a -> Exp Int -> Exp a Source #
x `complementBit` i
is the same as x `xor` bit i
testBit :: Exp a -> Exp Int -> Exp Bool Source #
Return True
if the n
th bit of the argument is 1
isSigned :: Exp a -> Exp Bool Source #
Return True
if the argument is a signed type.
shiftL :: Exp a -> Exp Int -> Exp a infixl 8 Source #
Shift the argument left by the specified number of bits (which must be non-negative).
unsafeShiftL :: Exp a -> Exp Int -> Exp a Source #
Shift the argument left by the specified number of bits. The result is
undefined for negative shift amounts and shift amounts greater or equal to
the finiteBitSize
.
shiftR :: Exp a -> Exp Int -> Exp a infixl 8 Source #
Shift the first argument right by the specified number of bits (which must be non-negative).
Right shifts perform sign extension on signed number types; i.e. they fill
the top bits with 1 if x
is negative and with 0 otherwise.
unsafeShiftR :: Exp a -> Exp Int -> Exp a Source #
Shift the first argument right by the specified number of bits. The
result is undefined for negative shift amounts and shift amounts greater or
equal to the finiteBitSize
.
rotateL :: Exp a -> Exp Int -> Exp a infixl 8 Source #
Rotate the argument left by the specified number of bits (which must be non-negative).
rotateR :: Exp a -> Exp Int -> Exp a infixl 8 Source #
Rotate the argument right by the specified number of bits (which must be non-negative).
popCount :: Exp a -> Exp Int Source #
Return the number of set bits in the argument. This number is known as the population count or the Hamming weight.
Instances
class Bits b => FiniteBits b where Source #
finiteBitSize :: Exp b -> Exp Int Source #
Return the number of bits in the type of the argument.
countLeadingZeros :: Exp b -> Exp Int Source #
Count the number of zero bits preceding the most significant set bit. This can be used to compute a base-2 logarithm via:
logBase2 x = finiteBitSize x - 1 - countLeadingZeros x
countTrailingZeros :: Exp b -> Exp Int Source #
Count the number of zero bits following the least significant set bit. The related find-first-set operation can be expressed in terms of this as:
findFirstSet x = 1 + countTrailingZeros x