base-4.11.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Bits

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

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.

Methods

(.&.) :: 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 #

shift x i shifts x 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 #

rotate x i rotates x 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.

zeroBits :: a Source #

zeroBits is the value with all bits unset.

The following laws ought to hold (for all valid bit indices n):

This method uses clearBit (bit 0) 0 as its default implementation (which ought to be equivalent to zeroBits for types which possess a 0th bit).

Since: 4.7.0.0

bit :: Int -> a Source #

bit i is a value with the ith bit set and all other bits clear.

Can be implemented using bitDefault if a is also an instance of Num.

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 nth bit of the argument is 1

Can be implemented using testBitDefault if a is also an instance of Num.

bitSizeMaybe :: a -> Maybe Int Source #

Return the number of bits in the type of the argument. The actual value of the argument is ignored. Returns Nothing for types that do not have a fixed bitsize, like Integer.

Since: 4.7.0.0

bitSize :: a -> Int Source #

Deprecated: Use bitSizeMaybe or finiteBitSize instead

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 Source #

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.

unsafeShiftL :: a -> Int -> 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 bitSize.

Defaults to shiftL unless defined explicitly by an instance.

Since: 4.5.0.0

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.

unsafeShiftR :: a -> Int -> a Source #

Shift the first argument right by the specified number of bits, which must be non-negative and smaller than the number of bits in the type.

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.

Defaults to shiftR unless defined explicitly by an instance.

Since: 4.5.0.0

rotateL :: a -> Int -> a infixl 8 Source #

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 infixl 8 Source #

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.

popCount :: a -> Int Source #

Return the number of set bits in the argument. This number is known as the population count or the Hamming weight.

Can be implemented using popCountDefault if a is also an instance of Num.

Since: 4.5.0.0

Instances
Bits Bool #

Interpret Bool as 1-bit bit-field

Since: 4.7.0.0

Instance details
Bits Int #

Since: 2.1

Instance details
Bits Int8 #

Since: 2.1

Instance details
Bits Int16 #

Since: 2.1

Instance details
Bits Int32 #

Since: 2.1

Instance details
Bits Int64 #

Since: 2.1

Instance details
Bits Integer #

Since: 2.1

Instance details
Bits Natural #

Since: 4.8.0.0

Instance details
Bits Word #

Since: 2.1

Instance details
Bits Word8 #

Since: 2.1

Instance details
Bits Word16 #

Since: 2.1

Instance details
Bits Word32 #

Since: 2.1

Instance details
Bits Word64 #

Since: 2.1

Instance details
Bits IntPtr # 
Instance details
Bits WordPtr # 
Instance details
Bits CUIntMax # 
Instance details
Bits CIntMax # 
Instance details
Bits CUIntPtr # 
Instance details
Bits CIntPtr # 
Instance details
Bits CSigAtomic # 
Instance details
Bits CWchar # 
Instance details
Bits CSize # 
Instance details
Bits CPtrdiff # 
Instance details
Bits CBool # 
Instance details
Bits CULLong # 
Instance details
Bits CLLong # 
Instance details
Bits CULong # 
Instance details
Bits CLong # 
Instance details
Bits CUInt # 
Instance details
Bits CInt # 
Instance details
Bits CUShort # 
Instance details
Bits CShort # 
Instance details
Bits CUChar # 
Instance details
Bits CSChar # 
Instance details
Bits CChar # 
Instance details
Bits Fd # 
Instance details
Bits CKey # 
Instance details
Bits CId # 
Instance details
Bits CFsFilCnt # 
Instance details
Bits CFsBlkCnt # 
Instance details
Bits CClockId # 
Instance details
Bits CBlkCnt # 
Instance details
Bits CBlkSize # 
Instance details
Bits CRLim # 
Instance details
Bits CTcflag # 
Instance details
Bits CUid # 
Instance details
Bits CNlink # 
Instance details
Bits CGid # 
Instance details
Bits CSsize # 
Instance details
Bits CPid # 
Instance details
Bits COff # 
Instance details
Bits CMode # 
Instance details
Bits CIno # 
Instance details
Bits CDev # 
Instance details
Bits a => Bits (Identity a) # 
Instance details
Bits a => Bits (Const a b) # 
Instance details

Methods

(.&.) :: Const a b -> Const a b -> Const a b Source #

(.|.) :: Const a b -> Const a b -> Const a b Source #

xor :: Const a b -> Const a b -> Const a b Source #

complement :: Const a b -> Const a b Source #

shift :: Const a b -> Int -> Const a b Source #

rotate :: Const a b -> Int -> Const a b Source #

zeroBits :: Const a b Source #

bit :: Int -> Const a b Source #

setBit :: Const a b -> Int -> Const a b Source #

clearBit :: Const a b -> Int -> Const a b Source #

complementBit :: Const a b -> Int -> Const a b Source #

testBit :: Const a b -> Int -> Bool Source #

bitSizeMaybe :: Const a b -> Maybe Int Source #

bitSize :: Const a b -> Int Source #

isSigned :: Const a b -> Bool Source #

shiftL :: Const a b -> Int -> Const a b Source #

unsafeShiftL :: Const a b -> Int -> Const a b Source #

shiftR :: Const a b -> Int -> Const a b Source #

unsafeShiftR :: Const a b -> Int -> Const a b Source #

rotateL :: Const a b -> Int -> Const a b Source #

rotateR :: Const a b -> Int -> Const a b Source #

popCount :: Const a b -> Int Source #

class Bits b => FiniteBits b where Source #

The FiniteBits class denotes types with a finite, fixed number of bits.

Since: 4.7.0.0

Minimal complete definition

finiteBitSize

Methods

finiteBitSize :: b -> Int Source #

Return the number of bits in the type of the argument. The actual value of the argument is ignored. Moreover, finiteBitSize is total, in contrast to the deprecated bitSize function it replaces.

finiteBitSize = bitSize
bitSizeMaybe = Just . finiteBitSize

Since: 4.7.0.0

countLeadingZeros :: b -> Int Source #

Count number of zero bits preceding the most significant set bit.

countLeadingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a)

countLeadingZeros can be used to compute log base 2 via

logBase2 x = finiteBitSize x - 1 - countLeadingZeros x

Note: The default implementation for this method is intentionally naive. However, the instances provided for the primitive integral types are implemented using CPU specific machine instructions.

Since: 4.8.0.0

countTrailingZeros :: b -> Int Source #

Count number of zero bits following the least significant set bit.

countTrailingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a)
countTrailingZeros . negate = countTrailingZeros

The related find-first-set operation can be expressed in terms of countTrailingZeros as follows

findFirstSet x = 1 + countTrailingZeros x

Note: The default implementation for this method is intentionally naive. However, the instances provided for the primitive integral types are implemented using CPU specific machine instructions.

Since: 4.8.0.0

Instances
FiniteBits Bool #

Since: 4.7.0.0

Instance details
FiniteBits Int #

Since: 4.6.0.0

Instance details
FiniteBits Int8 #

Since: 4.6.0.0

Instance details
FiniteBits Int16 #

Since: 4.6.0.0

Instance details
FiniteBits Int32 #

Since: 4.6.0.0

Instance details
FiniteBits Int64 #

Since: 4.6.0.0

Instance details
FiniteBits Word #

Since: 4.6.0.0

Instance details
FiniteBits Word8 #

Since: 4.6.0.0

Instance details
FiniteBits Word16 #

Since: 4.6.0.0

Instance details
FiniteBits Word32 #

Since: 4.6.0.0

Instance details
FiniteBits Word64 #

Since: 4.6.0.0

Instance details
FiniteBits IntPtr # 
Instance details
FiniteBits WordPtr # 
Instance details
FiniteBits CUIntMax # 
Instance details
FiniteBits CIntMax # 
Instance details
FiniteBits CUIntPtr # 
Instance details
FiniteBits CIntPtr # 
Instance details
FiniteBits CSigAtomic # 
Instance details
FiniteBits CWchar # 
Instance details
FiniteBits CSize # 
Instance details
FiniteBits CPtrdiff # 
Instance details
FiniteBits CBool # 
Instance details
FiniteBits CULLong # 
Instance details
FiniteBits CLLong # 
Instance details
FiniteBits CULong # 
Instance details
FiniteBits CLong # 
Instance details
FiniteBits CUInt # 
Instance details
FiniteBits CInt # 
Instance details
FiniteBits CUShort # 
Instance details
FiniteBits CShort # 
Instance details
FiniteBits CUChar # 
Instance details
FiniteBits CSChar # 
Instance details
FiniteBits CChar # 
Instance details
FiniteBits Fd # 
Instance details
FiniteBits CKey # 
Instance details
FiniteBits CId # 
Instance details
FiniteBits CFsFilCnt # 
Instance details
FiniteBits CFsBlkCnt # 
Instance details
FiniteBits CClockId # 
Instance details
FiniteBits CBlkCnt # 
Instance details
FiniteBits CBlkSize # 
Instance details
FiniteBits CRLim # 
Instance details
FiniteBits CTcflag # 
Instance details
FiniteBits CUid # 
Instance details
FiniteBits CNlink # 
Instance details
FiniteBits CGid # 
Instance details
FiniteBits CSsize # 
Instance details
FiniteBits CPid # 
Instance details
FiniteBits COff # 
Instance details
FiniteBits CMode # 
Instance details
FiniteBits CIno # 
Instance details
FiniteBits CDev # 
Instance details
FiniteBits a => FiniteBits (Identity a) # 
Instance details
FiniteBits a => FiniteBits (Const a b) # 
Instance details

bitDefault :: (Bits a, Num a) => Int -> a Source #

Default implementation for bit.

Note that: bitDefault i = 1 shiftL i

Since: 4.6.0.0

testBitDefault :: (Bits a, Num a) => a -> Int -> Bool Source #

Default implementation for testBit.

Note that: testBitDefault x i = (x .&. bit i) /= 0

Since: 4.6.0.0

popCountDefault :: (Bits a, Num a) => a -> Int Source #

Default implementation for popCount.

This implementation is intentionally naive. Instances are expected to provide an optimized implementation for their size.

Since: 4.6.0.0

toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b Source #

Attempt to convert an Integral type a to an Integral type b using the size of the types as measured by Bits methods.

A simpler version of this function is:

toIntegral :: (Integral a, Integral b) => a -> Maybe b
toIntegral x
  | toInteger x == y = Just (fromInteger y)
  | otherwise        = Nothing
  where
    y = toInteger x

This version requires going through Integer, which can be inefficient. However, toIntegralSized is optimized to allow GHC to statically determine the relative type sizes (as measured by bitSizeMaybe and isSigned) and avoid going through Integer for many types. (The implementation uses fromIntegral, which is itself optimized with rules for base types but may go through Integer for some type pairs.)

Since: 4.8.0.0