4.2. Bits

This module defines bitwise operations for signed and unsigned ints. Instances of class Bits for the Int and Integer types are available from this module, and instances for explicitly sized integral types are available from the Int (Section 4.18) and Word (Section 4.39) modules.

infixl 8 `shift`, `rotate`
infixl 7 .&.
infixl 6 `xor`
infixl 5 .|.

class Num a => 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

  bit i             = shift 0x1 i
  setBit x i        = x .|. bit i
  clearBit x i      = x .&. complement (bit i)
  complementBit x i = x `xor` bit i
  testBit x i       = (x .&. bit i) /= 0

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)

instance Bits Int
instance Bits Integer

Notes: