Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module defines bitwise operations for signed and unsigned integers.
- class Eq a => Bits a where
- (.&.) :: a -> a -> a
- (.|.) :: a -> a -> a
- xor :: a -> a -> a
- complement :: a -> a
- shift :: a -> Int -> a
- rotate :: a -> Int -> a
- bit :: Int -> a
- setBit :: a -> Int -> a
- clearBit :: a -> Int -> a
- complementBit :: a -> Int -> a
- testBit :: a -> Int -> Bool
- bitSize :: a -> Int
- isSigned :: a -> Bool
- shiftL :: a -> Int -> a
- shiftR :: a -> Int -> a
- rotateL :: a -> Int -> a
- rotateR :: a -> Int -> a
Documentation
class Eq a => Bits a where Source
The Bits
class defines bitwise operations over integral types.
- Bits are numbered from 0 with bit 0 being the least significant bit.
Minimal complete definition: .&.
, .|.
, xor
, complement
,
(shift
or (shiftL
and shiftR
)), (rotate
or (rotateL
and rotateR
)),
bitSize
, isSigned
, testBit
, bit
, and popCount
. The latter three can
be implemented using testBitDefault
, bitDefault
, and popCountDefault
, if
a
is also an instance of Num
.
(.&.), (.|.), xor, complement, (shift | shiftL, shiftR), (rotate | rotateL, rotateR), bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount
(.&.) :: a -> a -> a infixl 7 Source
Bitwise "and"
(.|.) :: a -> a -> a infixl 5 Source
Bitwise "or"
xor :: a -> a -> a infixl 6 Source
Bitwise "xor"
complement :: a -> a Source
Reverse all the bits in the argument
shift :: a -> Int -> 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.
An instance can define either this unified shift
or shiftL
and
shiftR
, depending on which is more convenient for the type in
question.
rotate :: a -> Int -> a infixl 8 Source
rotates rotate
x ix
left by i
bits if i
is positive,
or right by -i
bits otherwise.
For unbounded types like Integer
, rotate
is equivalent to shift
.
An instance can define either this unified rotate
or rotateL
and
rotateR
, depending on which is more convenient for the type in
question.
bit i
is a value with the i
th bit set and all other bits clear.
See also zeroBits
.
setBit :: a -> Int -> a Source
x `setBit` i
is the same as x .|. bit i
clearBit :: a -> Int -> a Source
x `clearBit` i
is the same as x .&. complement (bit i)
complementBit :: a -> Int -> a Source
x `complementBit` i
is the same as x `xor` bit i
testBit :: a -> Int -> Bool Source
Return True
if the n
th bit of the argument is 1
Return the number of bits in the type of the argument. The actual
value of the argument is ignored. The function bitSize
is
undefined for types that do not have a fixed bitsize, like Integer
.
Return True
if the argument is a signed type. The actual
value of the argument is ignored
shiftL :: a -> Int -> a infixl 8 Source
Shift the argument left by the specified number of bits (which must be non-negative).
An instance can define either this and shiftR
or the unified
shift
, depending on which is more convenient for the type in
question.
shiftR :: a -> Int -> a infixl 8 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 bitSize
.
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.
An instance can define either this and shiftL
or the unified
shift
, depending on which is more convenient for the type in
question.