Haskell Core Libraries (base package)ParentContentsIndex
Data.Bits
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Description
This module defines bitwise operations for signed and unsigned integers. Instances of the class Bits for the Int and Integer types are available from this module, and instances for explicitly sized integral types are available from the Data.Int and Data.Word modules.
Synopsis
class (Num 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 (Num a) => Bits a where

The Bits class defines bitwise operations over integral types.

  • Bits are numbered from 0 with bit 0 being the least significant bit.
Methods
(.&.) :: a -> a -> a
Bitwise "and"
(.|.) :: a -> a -> a
Bitwise "or"
xor :: a -> a -> a
Bitwise "xor"
complement :: a -> a
Reverse all the bits in the argument
shift :: a -> Int -> a

Shift the argument left by the specified number of bits. Right shifts (signed) are specified by giving a negative value.

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

Rotate the argument left by the specified number of bits. Right rotates are specified by giving a negative value.

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 :: Int -> a
bit i is a value with the ith bit set
setBit :: a -> Int -> a
x `setBit` i is the same as x .|. bit i
clearBit :: a -> Int -> a
x `clearBit` i is the same as x .&. complement (bit i)
complementBit :: a -> Int -> a
x `complementBit` i is the same as x `xor` bit i
testBit :: a -> Int -> Bool
Return True if the nth bit of the argument is 1
bitSize :: a -> Int
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.
isSigned :: a -> Bool
Return True if the argument is a signed type. The actual value of the argument is ignored
shiftL :: a -> Int -> a

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

Shift the argument right (signed) by the specified number of bits (which must be non-negative).

An instance can define either this and shiftL or the unified shift, depending on which is more convenient for the type in question.

rotateL :: a -> Int -> a

Rotate the argument left by the specified number of bits (which must be non-negative).

An instance can define either this and rotateR or the unified rotate, depending on which is more convenient for the type in question.

rotateR :: a -> Int -> a

Rotate the argument right by the specified number of bits (which must be non-negative).

An instance can define either this and rotateL or the unified rotate, depending on which is more convenient for the type in question.

Instances
Bits Int
Bits Integer
Bits CChar
Bits CSChar
Bits CUChar
Bits CShort
Bits CUShort
Bits CInt
Bits CUInt
Bits CLong
Bits CULong
Bits CLLong
Bits CULLong
Bits CPtrdiff
Bits CSize
Bits CWchar
Bits CSigAtomic
Bits CClock
Bits CTime
Bits Int8
Bits Int16
Bits Int32
Bits Int64
Bits Word
Bits Word8
Bits Word16
Bits Word32
Bits Word64
Bits CIno
Bits CMode
Bits COff
Bits CPid
Bits CSsize
Bits CGid
Bits CNlink
Bits CUid
Bits CTcflag
Bits CRLim
Bits Fd
Produced by Haddock version 0.4