This library defines bitwise operations for signed and unsigned ints.
module Bits where
infixl 8 `shift`, `rotate`
infixl 7 .&.
infixl 6 `xor`
infixl 5 .|.
class Bits a where
(.&.), (.|.), 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, shiftR :: Bits a => a -> Int -> a
rotateL, rotateR :: Bits a => a -> Int -> a
shiftL a i = shift a i
shiftR a i = shift a (-i)
rotateL a i = rotate a i
rotateR a i = rotate a (-i)
Notes:
bitSize
and isSigned
are like floatRadix
and floatDigits
-- they return parameters of the type of their argument rather than
of the particular argument they are applied to. bitSize
returns
the number of bits in the type (or Nothing
for unbounded types); and
isSigned
returns whether the type is signed or not. shift
performs sign extension on signed number types.
That is, right shifts fill the top bits with 1 if the number is negative
and with 0 otherwise.shift x i
and rotate x i
shift to the left if i
is
positive and to the right otherwise. bit i
is the value with the i'th bit set.