Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Data.Bits
Description
Synopsis
- class Eq a => Bits a where
- class Bits b => FiniteBits b where
- bitDefault :: (Bits a, Num a) => Int -> a
- testBitDefault :: (Bits a, Num a) => a -> Int -> Bool
- popCountDefault :: (Bits a, Num a) => a -> Int
- toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b
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 | shiftL, shiftR), (rotate | rotateL, rotateR), bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount
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 #
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.
zeroBits
is the value with all bits unset.
The following laws ought to hold (for all valid bit indices n
):
clearBit
zeroBits
n ==zeroBits
setBit
zeroBits
n ==bit
ntestBit
zeroBits
n == FalsepopCount
zeroBits
== 0
This method uses
as its default
implementation (which ought to be equivalent to clearBit
(bit
0) 0zeroBits
for
types which possess a 0th bit).
Since: 4.7.0.0
bit i
is a value with the i
th 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 n
th 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
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 an 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.
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
Methods
(.&.) :: Bool -> Bool -> Bool Source #
(.|.) :: Bool -> Bool -> Bool Source #
xor :: Bool -> Bool -> Bool Source #
complement :: Bool -> Bool Source #
shift :: Bool -> Int -> Bool Source #
rotate :: Bool -> Int -> Bool Source #
setBit :: Bool -> Int -> Bool Source #
clearBit :: Bool -> Int -> Bool Source #
complementBit :: Bool -> Int -> Bool Source #
testBit :: Bool -> Int -> Bool Source #
bitSizeMaybe :: Bool -> Maybe Int Source #
bitSize :: Bool -> Int Source #
isSigned :: Bool -> Bool Source #
shiftL :: Bool -> Int -> Bool Source #
unsafeShiftL :: Bool -> Int -> Bool Source #
shiftR :: Bool -> Int -> Bool Source #
unsafeShiftR :: Bool -> Int -> Bool Source #
rotateL :: Bool -> Int -> Bool Source #
Methods
(.&.) :: Int -> Int -> Int Source #
(.|.) :: Int -> Int -> Int Source #
xor :: Int -> Int -> Int Source #
complement :: Int -> Int Source #
shift :: Int -> Int -> Int Source #
rotate :: Int -> Int -> Int Source #
setBit :: Int -> Int -> Int Source #
clearBit :: Int -> Int -> Int Source #
complementBit :: Int -> Int -> Int Source #
testBit :: Int -> Int -> Bool Source #
bitSizeMaybe :: Int -> Maybe Int Source #
bitSize :: Int -> Int Source #
isSigned :: Int -> Bool Source #
shiftL :: Int -> Int -> Int Source #
unsafeShiftL :: Int -> Int -> Int Source #
shiftR :: Int -> Int -> Int Source #
unsafeShiftR :: Int -> Int -> Int Source #
rotateL :: Int -> Int -> Int Source #
Methods
(.&.) :: Int8 -> Int8 -> Int8 Source #
(.|.) :: Int8 -> Int8 -> Int8 Source #
xor :: Int8 -> Int8 -> Int8 Source #
complement :: Int8 -> Int8 Source #
shift :: Int8 -> Int -> Int8 Source #
rotate :: Int8 -> Int -> Int8 Source #
setBit :: Int8 -> Int -> Int8 Source #
clearBit :: Int8 -> Int -> Int8 Source #
complementBit :: Int8 -> Int -> Int8 Source #
testBit :: Int8 -> Int -> Bool Source #
bitSizeMaybe :: Int8 -> Maybe Int Source #
bitSize :: Int8 -> Int Source #
isSigned :: Int8 -> Bool Source #
shiftL :: Int8 -> Int -> Int8 Source #
unsafeShiftL :: Int8 -> Int -> Int8 Source #
shiftR :: Int8 -> Int -> Int8 Source #
unsafeShiftR :: Int8 -> Int -> Int8 Source #
rotateL :: Int8 -> Int -> Int8 Source #
Methods
(.&.) :: Int16 -> Int16 -> Int16 Source #
(.|.) :: Int16 -> Int16 -> Int16 Source #
xor :: Int16 -> Int16 -> Int16 Source #
complement :: Int16 -> Int16 Source #
shift :: Int16 -> Int -> Int16 Source #
rotate :: Int16 -> Int -> Int16 Source #
setBit :: Int16 -> Int -> Int16 Source #
clearBit :: Int16 -> Int -> Int16 Source #
complementBit :: Int16 -> Int -> Int16 Source #
testBit :: Int16 -> Int -> Bool Source #
bitSizeMaybe :: Int16 -> Maybe Int Source #
bitSize :: Int16 -> Int Source #
isSigned :: Int16 -> Bool Source #
shiftL :: Int16 -> Int -> Int16 Source #
unsafeShiftL :: Int16 -> Int -> Int16 Source #
shiftR :: Int16 -> Int -> Int16 Source #
unsafeShiftR :: Int16 -> Int -> Int16 Source #
rotateL :: Int16 -> Int -> Int16 Source #
Methods
(.&.) :: Int32 -> Int32 -> Int32 Source #
(.|.) :: Int32 -> Int32 -> Int32 Source #
xor :: Int32 -> Int32 -> Int32 Source #
complement :: Int32 -> Int32 Source #
shift :: Int32 -> Int -> Int32 Source #
rotate :: Int32 -> Int -> Int32 Source #
setBit :: Int32 -> Int -> Int32 Source #
clearBit :: Int32 -> Int -> Int32 Source #
complementBit :: Int32 -> Int -> Int32 Source #
testBit :: Int32 -> Int -> Bool Source #
bitSizeMaybe :: Int32 -> Maybe Int Source #
bitSize :: Int32 -> Int Source #
isSigned :: Int32 -> Bool Source #
shiftL :: Int32 -> Int -> Int32 Source #
unsafeShiftL :: Int32 -> Int -> Int32 Source #
shiftR :: Int32 -> Int -> Int32 Source #
unsafeShiftR :: Int32 -> Int -> Int32 Source #
rotateL :: Int32 -> Int -> Int32 Source #
Methods
(.&.) :: Int64 -> Int64 -> Int64 Source #
(.|.) :: Int64 -> Int64 -> Int64 Source #
xor :: Int64 -> Int64 -> Int64 Source #
complement :: Int64 -> Int64 Source #
shift :: Int64 -> Int -> Int64 Source #
rotate :: Int64 -> Int -> Int64 Source #
setBit :: Int64 -> Int -> Int64 Source #
clearBit :: Int64 -> Int -> Int64 Source #
complementBit :: Int64 -> Int -> Int64 Source #
testBit :: Int64 -> Int -> Bool Source #
bitSizeMaybe :: Int64 -> Maybe Int Source #
bitSize :: Int64 -> Int Source #
isSigned :: Int64 -> Bool Source #
shiftL :: Int64 -> Int -> Int64 Source #
unsafeShiftL :: Int64 -> Int -> Int64 Source #
shiftR :: Int64 -> Int -> Int64 Source #
unsafeShiftR :: Int64 -> Int -> Int64 Source #
rotateL :: Int64 -> Int -> Int64 Source #
Methods
(.&.) :: Integer -> Integer -> Integer Source #
(.|.) :: Integer -> Integer -> Integer Source #
xor :: Integer -> Integer -> Integer Source #
complement :: Integer -> Integer Source #
shift :: Integer -> Int -> Integer Source #
rotate :: Integer -> Int -> Integer Source #
bit :: Int -> Integer Source #
setBit :: Integer -> Int -> Integer Source #
clearBit :: Integer -> Int -> Integer Source #
complementBit :: Integer -> Int -> Integer Source #
testBit :: Integer -> Int -> Bool Source #
bitSizeMaybe :: Integer -> Maybe Int Source #
bitSize :: Integer -> Int Source #
isSigned :: Integer -> Bool Source #
shiftL :: Integer -> Int -> Integer Source #
unsafeShiftL :: Integer -> Int -> Integer Source #
shiftR :: Integer -> Int -> Integer Source #
unsafeShiftR :: Integer -> Int -> Integer Source #
rotateL :: Integer -> Int -> Integer Source #
Methods
(.&.) :: Natural -> Natural -> Natural Source #
(.|.) :: Natural -> Natural -> Natural Source #
xor :: Natural -> Natural -> Natural Source #
complement :: Natural -> Natural Source #
shift :: Natural -> Int -> Natural Source #
rotate :: Natural -> Int -> Natural Source #
bit :: Int -> Natural Source #
setBit :: Natural -> Int -> Natural Source #
clearBit :: Natural -> Int -> Natural Source #
complementBit :: Natural -> Int -> Natural Source #
testBit :: Natural -> Int -> Bool Source #
bitSizeMaybe :: Natural -> Maybe Int Source #
bitSize :: Natural -> Int Source #
isSigned :: Natural -> Bool Source #
shiftL :: Natural -> Int -> Natural Source #
unsafeShiftL :: Natural -> Int -> Natural Source #
shiftR :: Natural -> Int -> Natural Source #
unsafeShiftR :: Natural -> Int -> Natural Source #
rotateL :: Natural -> Int -> Natural Source #
Methods
(.&.) :: Word -> Word -> Word Source #
(.|.) :: Word -> Word -> Word Source #
xor :: Word -> Word -> Word Source #
complement :: Word -> Word Source #
shift :: Word -> Int -> Word Source #
rotate :: Word -> Int -> Word Source #
setBit :: Word -> Int -> Word Source #
clearBit :: Word -> Int -> Word Source #
complementBit :: Word -> Int -> Word Source #
testBit :: Word -> Int -> Bool Source #
bitSizeMaybe :: Word -> Maybe Int Source #
bitSize :: Word -> Int Source #
isSigned :: Word -> Bool Source #
shiftL :: Word -> Int -> Word Source #
unsafeShiftL :: Word -> Int -> Word Source #
shiftR :: Word -> Int -> Word Source #
unsafeShiftR :: Word -> Int -> Word Source #
rotateL :: Word -> Int -> Word Source #
Methods
(.&.) :: Word8 -> Word8 -> Word8 Source #
(.|.) :: Word8 -> Word8 -> Word8 Source #
xor :: Word8 -> Word8 -> Word8 Source #
complement :: Word8 -> Word8 Source #
shift :: Word8 -> Int -> Word8 Source #
rotate :: Word8 -> Int -> Word8 Source #
setBit :: Word8 -> Int -> Word8 Source #
clearBit :: Word8 -> Int -> Word8 Source #
complementBit :: Word8 -> Int -> Word8 Source #
testBit :: Word8 -> Int -> Bool Source #
bitSizeMaybe :: Word8 -> Maybe Int Source #
bitSize :: Word8 -> Int Source #
isSigned :: Word8 -> Bool Source #
shiftL :: Word8 -> Int -> Word8 Source #
unsafeShiftL :: Word8 -> Int -> Word8 Source #
shiftR :: Word8 -> Int -> Word8 Source #
unsafeShiftR :: Word8 -> Int -> Word8 Source #
rotateL :: Word8 -> Int -> Word8 Source #
Methods
(.&.) :: Word16 -> Word16 -> Word16 Source #
(.|.) :: Word16 -> Word16 -> Word16 Source #
xor :: Word16 -> Word16 -> Word16 Source #
complement :: Word16 -> Word16 Source #
shift :: Word16 -> Int -> Word16 Source #
rotate :: Word16 -> Int -> Word16 Source #
setBit :: Word16 -> Int -> Word16 Source #
clearBit :: Word16 -> Int -> Word16 Source #
complementBit :: Word16 -> Int -> Word16 Source #
testBit :: Word16 -> Int -> Bool Source #
bitSizeMaybe :: Word16 -> Maybe Int Source #
bitSize :: Word16 -> Int Source #
isSigned :: Word16 -> Bool Source #
shiftL :: Word16 -> Int -> Word16 Source #
unsafeShiftL :: Word16 -> Int -> Word16 Source #
shiftR :: Word16 -> Int -> Word16 Source #
unsafeShiftR :: Word16 -> Int -> Word16 Source #
rotateL :: Word16 -> Int -> Word16 Source #
Methods
(.&.) :: Word32 -> Word32 -> Word32 Source #
(.|.) :: Word32 -> Word32 -> Word32 Source #
xor :: Word32 -> Word32 -> Word32 Source #
complement :: Word32 -> Word32 Source #
shift :: Word32 -> Int -> Word32 Source #
rotate :: Word32 -> Int -> Word32 Source #
setBit :: Word32 -> Int -> Word32 Source #
clearBit :: Word32 -> Int -> Word32 Source #
complementBit :: Word32 -> Int -> Word32 Source #
testBit :: Word32 -> Int -> Bool Source #
bitSizeMaybe :: Word32 -> Maybe Int Source #
bitSize :: Word32 -> Int Source #
isSigned :: Word32 -> Bool Source #
shiftL :: Word32 -> Int -> Word32 Source #
unsafeShiftL :: Word32 -> Int -> Word32 Source #
shiftR :: Word32 -> Int -> Word32 Source #
unsafeShiftR :: Word32 -> Int -> Word32 Source #
rotateL :: Word32 -> Int -> Word32 Source #
Methods
(.&.) :: Word64 -> Word64 -> Word64 Source #
(.|.) :: Word64 -> Word64 -> Word64 Source #
xor :: Word64 -> Word64 -> Word64 Source #
complement :: Word64 -> Word64 Source #
shift :: Word64 -> Int -> Word64 Source #
rotate :: Word64 -> Int -> Word64 Source #
setBit :: Word64 -> Int -> Word64 Source #
clearBit :: Word64 -> Int -> Word64 Source #
complementBit :: Word64 -> Int -> Word64 Source #
testBit :: Word64 -> Int -> Bool Source #
bitSizeMaybe :: Word64 -> Maybe Int Source #
bitSize :: Word64 -> Int Source #
isSigned :: Word64 -> Bool Source #
shiftL :: Word64 -> Int -> Word64 Source #
unsafeShiftL :: Word64 -> Int -> Word64 Source #
shiftR :: Word64 -> Int -> Word64 Source #
unsafeShiftR :: Word64 -> Int -> Word64 Source #
rotateL :: Word64 -> Int -> Word64 Source #
Methods
(.&.) :: IntPtr -> IntPtr -> IntPtr Source #
(.|.) :: IntPtr -> IntPtr -> IntPtr Source #
xor :: IntPtr -> IntPtr -> IntPtr Source #
complement :: IntPtr -> IntPtr Source #
shift :: IntPtr -> Int -> IntPtr Source #
rotate :: IntPtr -> Int -> IntPtr Source #
setBit :: IntPtr -> Int -> IntPtr Source #
clearBit :: IntPtr -> Int -> IntPtr Source #
complementBit :: IntPtr -> Int -> IntPtr Source #
testBit :: IntPtr -> Int -> Bool Source #
bitSizeMaybe :: IntPtr -> Maybe Int Source #
bitSize :: IntPtr -> Int Source #
isSigned :: IntPtr -> Bool Source #
shiftL :: IntPtr -> Int -> IntPtr Source #
unsafeShiftL :: IntPtr -> Int -> IntPtr Source #
shiftR :: IntPtr -> Int -> IntPtr Source #
unsafeShiftR :: IntPtr -> Int -> IntPtr Source #
rotateL :: IntPtr -> Int -> IntPtr Source #
Methods
(.&.) :: WordPtr -> WordPtr -> WordPtr Source #
(.|.) :: WordPtr -> WordPtr -> WordPtr Source #
xor :: WordPtr -> WordPtr -> WordPtr Source #
complement :: WordPtr -> WordPtr Source #
shift :: WordPtr -> Int -> WordPtr Source #
rotate :: WordPtr -> Int -> WordPtr Source #
bit :: Int -> WordPtr Source #
setBit :: WordPtr -> Int -> WordPtr Source #
clearBit :: WordPtr -> Int -> WordPtr Source #
complementBit :: WordPtr -> Int -> WordPtr Source #
testBit :: WordPtr -> Int -> Bool Source #
bitSizeMaybe :: WordPtr -> Maybe Int Source #
bitSize :: WordPtr -> Int Source #
isSigned :: WordPtr -> Bool Source #
shiftL :: WordPtr -> Int -> WordPtr Source #
unsafeShiftL :: WordPtr -> Int -> WordPtr Source #
shiftR :: WordPtr -> Int -> WordPtr Source #
unsafeShiftR :: WordPtr -> Int -> WordPtr Source #
rotateL :: WordPtr -> Int -> WordPtr Source #
Methods
(.&.) :: CUIntMax -> CUIntMax -> CUIntMax Source #
(.|.) :: CUIntMax -> CUIntMax -> CUIntMax Source #
xor :: CUIntMax -> CUIntMax -> CUIntMax Source #
complement :: CUIntMax -> CUIntMax Source #
shift :: CUIntMax -> Int -> CUIntMax Source #
rotate :: CUIntMax -> Int -> CUIntMax Source #
bit :: Int -> CUIntMax Source #
setBit :: CUIntMax -> Int -> CUIntMax Source #
clearBit :: CUIntMax -> Int -> CUIntMax Source #
complementBit :: CUIntMax -> Int -> CUIntMax Source #
testBit :: CUIntMax -> Int -> Bool Source #
bitSizeMaybe :: CUIntMax -> Maybe Int Source #
bitSize :: CUIntMax -> Int Source #
isSigned :: CUIntMax -> Bool Source #
shiftL :: CUIntMax -> Int -> CUIntMax Source #
unsafeShiftL :: CUIntMax -> Int -> CUIntMax Source #
shiftR :: CUIntMax -> Int -> CUIntMax Source #
unsafeShiftR :: CUIntMax -> Int -> CUIntMax Source #
rotateL :: CUIntMax -> Int -> CUIntMax Source #
Methods
(.&.) :: CIntMax -> CIntMax -> CIntMax Source #
(.|.) :: CIntMax -> CIntMax -> CIntMax Source #
xor :: CIntMax -> CIntMax -> CIntMax Source #
complement :: CIntMax -> CIntMax Source #
shift :: CIntMax -> Int -> CIntMax Source #
rotate :: CIntMax -> Int -> CIntMax Source #
bit :: Int -> CIntMax Source #
setBit :: CIntMax -> Int -> CIntMax Source #
clearBit :: CIntMax -> Int -> CIntMax Source #
complementBit :: CIntMax -> Int -> CIntMax Source #
testBit :: CIntMax -> Int -> Bool Source #
bitSizeMaybe :: CIntMax -> Maybe Int Source #
bitSize :: CIntMax -> Int Source #
isSigned :: CIntMax -> Bool Source #
shiftL :: CIntMax -> Int -> CIntMax Source #
unsafeShiftL :: CIntMax -> Int -> CIntMax Source #
shiftR :: CIntMax -> Int -> CIntMax Source #
unsafeShiftR :: CIntMax -> Int -> CIntMax Source #
rotateL :: CIntMax -> Int -> CIntMax Source #
Methods
(.&.) :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
(.|.) :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
xor :: CUIntPtr -> CUIntPtr -> CUIntPtr Source #
complement :: CUIntPtr -> CUIntPtr Source #
shift :: CUIntPtr -> Int -> CUIntPtr Source #
rotate :: CUIntPtr -> Int -> CUIntPtr Source #
bit :: Int -> CUIntPtr Source #
setBit :: CUIntPtr -> Int -> CUIntPtr Source #
clearBit :: CUIntPtr -> Int -> CUIntPtr Source #
complementBit :: CUIntPtr -> Int -> CUIntPtr Source #
testBit :: CUIntPtr -> Int -> Bool Source #
bitSizeMaybe :: CUIntPtr -> Maybe Int Source #
bitSize :: CUIntPtr -> Int Source #
isSigned :: CUIntPtr -> Bool Source #
shiftL :: CUIntPtr -> Int -> CUIntPtr Source #
unsafeShiftL :: CUIntPtr -> Int -> CUIntPtr Source #
shiftR :: CUIntPtr -> Int -> CUIntPtr Source #
unsafeShiftR :: CUIntPtr -> Int -> CUIntPtr Source #
rotateL :: CUIntPtr -> Int -> CUIntPtr Source #
Methods
(.&.) :: CIntPtr -> CIntPtr -> CIntPtr Source #
(.|.) :: CIntPtr -> CIntPtr -> CIntPtr Source #
xor :: CIntPtr -> CIntPtr -> CIntPtr Source #
complement :: CIntPtr -> CIntPtr Source #
shift :: CIntPtr -> Int -> CIntPtr Source #
rotate :: CIntPtr -> Int -> CIntPtr Source #
bit :: Int -> CIntPtr Source #
setBit :: CIntPtr -> Int -> CIntPtr Source #
clearBit :: CIntPtr -> Int -> CIntPtr Source #
complementBit :: CIntPtr -> Int -> CIntPtr Source #
testBit :: CIntPtr -> Int -> Bool Source #
bitSizeMaybe :: CIntPtr -> Maybe Int Source #
bitSize :: CIntPtr -> Int Source #
isSigned :: CIntPtr -> Bool Source #
shiftL :: CIntPtr -> Int -> CIntPtr Source #
unsafeShiftL :: CIntPtr -> Int -> CIntPtr Source #
shiftR :: CIntPtr -> Int -> CIntPtr Source #
unsafeShiftR :: CIntPtr -> Int -> CIntPtr Source #
rotateL :: CIntPtr -> Int -> CIntPtr Source #
Methods
(.&.) :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
(.|.) :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
xor :: CSigAtomic -> CSigAtomic -> CSigAtomic Source #
complement :: CSigAtomic -> CSigAtomic Source #
shift :: CSigAtomic -> Int -> CSigAtomic Source #
rotate :: CSigAtomic -> Int -> CSigAtomic Source #
zeroBits :: CSigAtomic Source #
bit :: Int -> CSigAtomic Source #
setBit :: CSigAtomic -> Int -> CSigAtomic Source #
clearBit :: CSigAtomic -> Int -> CSigAtomic Source #
complementBit :: CSigAtomic -> Int -> CSigAtomic Source #
testBit :: CSigAtomic -> Int -> Bool Source #
bitSizeMaybe :: CSigAtomic -> Maybe Int Source #
bitSize :: CSigAtomic -> Int Source #
isSigned :: CSigAtomic -> Bool Source #
shiftL :: CSigAtomic -> Int -> CSigAtomic Source #
unsafeShiftL :: CSigAtomic -> Int -> CSigAtomic Source #
shiftR :: CSigAtomic -> Int -> CSigAtomic Source #
unsafeShiftR :: CSigAtomic -> Int -> CSigAtomic Source #
rotateL :: CSigAtomic -> Int -> CSigAtomic Source #
rotateR :: CSigAtomic -> Int -> CSigAtomic Source #
popCount :: CSigAtomic -> Int Source #
Methods
(.&.) :: CWchar -> CWchar -> CWchar Source #
(.|.) :: CWchar -> CWchar -> CWchar Source #
xor :: CWchar -> CWchar -> CWchar Source #
complement :: CWchar -> CWchar Source #
shift :: CWchar -> Int -> CWchar Source #
rotate :: CWchar -> Int -> CWchar Source #
setBit :: CWchar -> Int -> CWchar Source #
clearBit :: CWchar -> Int -> CWchar Source #
complementBit :: CWchar -> Int -> CWchar Source #
testBit :: CWchar -> Int -> Bool Source #
bitSizeMaybe :: CWchar -> Maybe Int Source #
bitSize :: CWchar -> Int Source #
isSigned :: CWchar -> Bool Source #
shiftL :: CWchar -> Int -> CWchar Source #
unsafeShiftL :: CWchar -> Int -> CWchar Source #
shiftR :: CWchar -> Int -> CWchar Source #
unsafeShiftR :: CWchar -> Int -> CWchar Source #
rotateL :: CWchar -> Int -> CWchar Source #
Methods
(.&.) :: CSize -> CSize -> CSize Source #
(.|.) :: CSize -> CSize -> CSize Source #
xor :: CSize -> CSize -> CSize Source #
complement :: CSize -> CSize Source #
shift :: CSize -> Int -> CSize Source #
rotate :: CSize -> Int -> CSize Source #
setBit :: CSize -> Int -> CSize Source #
clearBit :: CSize -> Int -> CSize Source #
complementBit :: CSize -> Int -> CSize Source #
testBit :: CSize -> Int -> Bool Source #
bitSizeMaybe :: CSize -> Maybe Int Source #
bitSize :: CSize -> Int Source #
isSigned :: CSize -> Bool Source #
shiftL :: CSize -> Int -> CSize Source #
unsafeShiftL :: CSize -> Int -> CSize Source #
shiftR :: CSize -> Int -> CSize Source #
unsafeShiftR :: CSize -> Int -> CSize Source #
rotateL :: CSize -> Int -> CSize Source #
Methods
(.&.) :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
(.|.) :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
xor :: CPtrdiff -> CPtrdiff -> CPtrdiff Source #
complement :: CPtrdiff -> CPtrdiff Source #
shift :: CPtrdiff -> Int -> CPtrdiff Source #
rotate :: CPtrdiff -> Int -> CPtrdiff Source #
bit :: Int -> CPtrdiff Source #
setBit :: CPtrdiff -> Int -> CPtrdiff Source #
clearBit :: CPtrdiff -> Int -> CPtrdiff Source #
complementBit :: CPtrdiff -> Int -> CPtrdiff Source #
testBit :: CPtrdiff -> Int -> Bool Source #
bitSizeMaybe :: CPtrdiff -> Maybe Int Source #
bitSize :: CPtrdiff -> Int Source #
isSigned :: CPtrdiff -> Bool Source #
shiftL :: CPtrdiff -> Int -> CPtrdiff Source #
unsafeShiftL :: CPtrdiff -> Int -> CPtrdiff Source #
shiftR :: CPtrdiff -> Int -> CPtrdiff Source #
unsafeShiftR :: CPtrdiff -> Int -> CPtrdiff Source #
rotateL :: CPtrdiff -> Int -> CPtrdiff Source #
Methods
(.&.) :: CBool -> CBool -> CBool Source #
(.|.) :: CBool -> CBool -> CBool Source #
xor :: CBool -> CBool -> CBool Source #
complement :: CBool -> CBool Source #
shift :: CBool -> Int -> CBool Source #
rotate :: CBool -> Int -> CBool Source #
setBit :: CBool -> Int -> CBool Source #
clearBit :: CBool -> Int -> CBool Source #
complementBit :: CBool -> Int -> CBool Source #
testBit :: CBool -> Int -> Bool Source #
bitSizeMaybe :: CBool -> Maybe Int Source #
bitSize :: CBool -> Int Source #
isSigned :: CBool -> Bool Source #
shiftL :: CBool -> Int -> CBool Source #
unsafeShiftL :: CBool -> Int -> CBool Source #
shiftR :: CBool -> Int -> CBool Source #
unsafeShiftR :: CBool -> Int -> CBool Source #
rotateL :: CBool -> Int -> CBool Source #
Methods
(.&.) :: CULLong -> CULLong -> CULLong Source #
(.|.) :: CULLong -> CULLong -> CULLong Source #
xor :: CULLong -> CULLong -> CULLong Source #
complement :: CULLong -> CULLong Source #
shift :: CULLong -> Int -> CULLong Source #
rotate :: CULLong -> Int -> CULLong Source #
bit :: Int -> CULLong Source #
setBit :: CULLong -> Int -> CULLong Source #
clearBit :: CULLong -> Int -> CULLong Source #
complementBit :: CULLong -> Int -> CULLong Source #
testBit :: CULLong -> Int -> Bool Source #
bitSizeMaybe :: CULLong -> Maybe Int Source #
bitSize :: CULLong -> Int Source #
isSigned :: CULLong -> Bool Source #
shiftL :: CULLong -> Int -> CULLong Source #
unsafeShiftL :: CULLong -> Int -> CULLong Source #
shiftR :: CULLong -> Int -> CULLong Source #
unsafeShiftR :: CULLong -> Int -> CULLong Source #
rotateL :: CULLong -> Int -> CULLong Source #
Methods
(.&.) :: CLLong -> CLLong -> CLLong Source #
(.|.) :: CLLong -> CLLong -> CLLong Source #
xor :: CLLong -> CLLong -> CLLong Source #
complement :: CLLong -> CLLong Source #
shift :: CLLong -> Int -> CLLong Source #
rotate :: CLLong -> Int -> CLLong Source #
setBit :: CLLong -> Int -> CLLong Source #
clearBit :: CLLong -> Int -> CLLong Source #
complementBit :: CLLong -> Int -> CLLong Source #
testBit :: CLLong -> Int -> Bool Source #
bitSizeMaybe :: CLLong -> Maybe Int Source #
bitSize :: CLLong -> Int Source #
isSigned :: CLLong -> Bool Source #
shiftL :: CLLong -> Int -> CLLong Source #
unsafeShiftL :: CLLong -> Int -> CLLong Source #
shiftR :: CLLong -> Int -> CLLong Source #
unsafeShiftR :: CLLong -> Int -> CLLong Source #
rotateL :: CLLong -> Int -> CLLong Source #
Methods
(.&.) :: CULong -> CULong -> CULong Source #
(.|.) :: CULong -> CULong -> CULong Source #
xor :: CULong -> CULong -> CULong Source #
complement :: CULong -> CULong Source #
shift :: CULong -> Int -> CULong Source #
rotate :: CULong -> Int -> CULong Source #
setBit :: CULong -> Int -> CULong Source #
clearBit :: CULong -> Int -> CULong Source #
complementBit :: CULong -> Int -> CULong Source #
testBit :: CULong -> Int -> Bool Source #
bitSizeMaybe :: CULong -> Maybe Int Source #
bitSize :: CULong -> Int Source #
isSigned :: CULong -> Bool Source #
shiftL :: CULong -> Int -> CULong Source #
unsafeShiftL :: CULong -> Int -> CULong Source #
shiftR :: CULong -> Int -> CULong Source #
unsafeShiftR :: CULong -> Int -> CULong Source #
rotateL :: CULong -> Int -> CULong Source #
Methods
(.&.) :: CLong -> CLong -> CLong Source #
(.|.) :: CLong -> CLong -> CLong Source #
xor :: CLong -> CLong -> CLong Source #
complement :: CLong -> CLong Source #
shift :: CLong -> Int -> CLong Source #
rotate :: CLong -> Int -> CLong Source #
setBit :: CLong -> Int -> CLong Source #
clearBit :: CLong -> Int -> CLong Source #
complementBit :: CLong -> Int -> CLong Source #
testBit :: CLong -> Int -> Bool Source #
bitSizeMaybe :: CLong -> Maybe Int Source #
bitSize :: CLong -> Int Source #
isSigned :: CLong -> Bool Source #
shiftL :: CLong -> Int -> CLong Source #
unsafeShiftL :: CLong -> Int -> CLong Source #
shiftR :: CLong -> Int -> CLong Source #
unsafeShiftR :: CLong -> Int -> CLong Source #
rotateL :: CLong -> Int -> CLong Source #
Methods
(.&.) :: CUInt -> CUInt -> CUInt Source #
(.|.) :: CUInt -> CUInt -> CUInt Source #
xor :: CUInt -> CUInt -> CUInt Source #
complement :: CUInt -> CUInt Source #
shift :: CUInt -> Int -> CUInt Source #
rotate :: CUInt -> Int -> CUInt Source #
setBit :: CUInt -> Int -> CUInt Source #
clearBit :: CUInt -> Int -> CUInt Source #
complementBit :: CUInt -> Int -> CUInt Source #
testBit :: CUInt -> Int -> Bool Source #
bitSizeMaybe :: CUInt -> Maybe Int Source #
bitSize :: CUInt -> Int Source #
isSigned :: CUInt -> Bool Source #
shiftL :: CUInt -> Int -> CUInt Source #
unsafeShiftL :: CUInt -> Int -> CUInt Source #
shiftR :: CUInt -> Int -> CUInt Source #
unsafeShiftR :: CUInt -> Int -> CUInt Source #
rotateL :: CUInt -> Int -> CUInt Source #
Methods
(.&.) :: CInt -> CInt -> CInt Source #
(.|.) :: CInt -> CInt -> CInt Source #
xor :: CInt -> CInt -> CInt Source #
complement :: CInt -> CInt Source #
shift :: CInt -> Int -> CInt Source #
rotate :: CInt -> Int -> CInt Source #
setBit :: CInt -> Int -> CInt Source #
clearBit :: CInt -> Int -> CInt Source #
complementBit :: CInt -> Int -> CInt Source #
testBit :: CInt -> Int -> Bool Source #
bitSizeMaybe :: CInt -> Maybe Int Source #
bitSize :: CInt -> Int Source #
isSigned :: CInt -> Bool Source #
shiftL :: CInt -> Int -> CInt Source #
unsafeShiftL :: CInt -> Int -> CInt Source #
shiftR :: CInt -> Int -> CInt Source #
unsafeShiftR :: CInt -> Int -> CInt Source #
rotateL :: CInt -> Int -> CInt Source #
Methods
(.&.) :: CUShort -> CUShort -> CUShort Source #
(.|.) :: CUShort -> CUShort -> CUShort Source #
xor :: CUShort -> CUShort -> CUShort Source #
complement :: CUShort -> CUShort Source #
shift :: CUShort -> Int -> CUShort Source #
rotate :: CUShort -> Int -> CUShort Source #
bit :: Int -> CUShort Source #
setBit :: CUShort -> Int -> CUShort Source #
clearBit :: CUShort -> Int -> CUShort Source #
complementBit :: CUShort -> Int -> CUShort Source #
testBit :: CUShort -> Int -> Bool Source #
bitSizeMaybe :: CUShort -> Maybe Int Source #
bitSize :: CUShort -> Int Source #
isSigned :: CUShort -> Bool Source #
shiftL :: CUShort -> Int -> CUShort Source #
unsafeShiftL :: CUShort -> Int -> CUShort Source #
shiftR :: CUShort -> Int -> CUShort Source #
unsafeShiftR :: CUShort -> Int -> CUShort Source #
rotateL :: CUShort -> Int -> CUShort Source #
Methods
(.&.) :: CShort -> CShort -> CShort Source #
(.|.) :: CShort -> CShort -> CShort Source #
xor :: CShort -> CShort -> CShort Source #
complement :: CShort -> CShort Source #
shift :: CShort -> Int -> CShort Source #
rotate :: CShort -> Int -> CShort Source #
setBit :: CShort -> Int -> CShort Source #
clearBit :: CShort -> Int -> CShort Source #
complementBit :: CShort -> Int -> CShort Source #
testBit :: CShort -> Int -> Bool Source #
bitSizeMaybe :: CShort -> Maybe Int Source #
bitSize :: CShort -> Int Source #
isSigned :: CShort -> Bool Source #
shiftL :: CShort -> Int -> CShort Source #
unsafeShiftL :: CShort -> Int -> CShort Source #
shiftR :: CShort -> Int -> CShort Source #
unsafeShiftR :: CShort -> Int -> CShort Source #
rotateL :: CShort -> Int -> CShort Source #
Methods
(.&.) :: CUChar -> CUChar -> CUChar Source #
(.|.) :: CUChar -> CUChar -> CUChar Source #
xor :: CUChar -> CUChar -> CUChar Source #
complement :: CUChar -> CUChar Source #
shift :: CUChar -> Int -> CUChar Source #
rotate :: CUChar -> Int -> CUChar Source #
setBit :: CUChar -> Int -> CUChar Source #
clearBit :: CUChar -> Int -> CUChar Source #
complementBit :: CUChar -> Int -> CUChar Source #
testBit :: CUChar -> Int -> Bool Source #
bitSizeMaybe :: CUChar -> Maybe Int Source #
bitSize :: CUChar -> Int Source #
isSigned :: CUChar -> Bool Source #
shiftL :: CUChar -> Int -> CUChar Source #
unsafeShiftL :: CUChar -> Int -> CUChar Source #
shiftR :: CUChar -> Int -> CUChar Source #
unsafeShiftR :: CUChar -> Int -> CUChar Source #
rotateL :: CUChar -> Int -> CUChar Source #
Methods
(.&.) :: CSChar -> CSChar -> CSChar Source #
(.|.) :: CSChar -> CSChar -> CSChar Source #
xor :: CSChar -> CSChar -> CSChar Source #
complement :: CSChar -> CSChar Source #
shift :: CSChar -> Int -> CSChar Source #
rotate :: CSChar -> Int -> CSChar Source #
setBit :: CSChar -> Int -> CSChar Source #
clearBit :: CSChar -> Int -> CSChar Source #
complementBit :: CSChar -> Int -> CSChar Source #
testBit :: CSChar -> Int -> Bool Source #
bitSizeMaybe :: CSChar -> Maybe Int Source #
bitSize :: CSChar -> Int Source #
isSigned :: CSChar -> Bool Source #
shiftL :: CSChar -> Int -> CSChar Source #
unsafeShiftL :: CSChar -> Int -> CSChar Source #
shiftR :: CSChar -> Int -> CSChar Source #
unsafeShiftR :: CSChar -> Int -> CSChar Source #
rotateL :: CSChar -> Int -> CSChar Source #
Methods
(.&.) :: CChar -> CChar -> CChar Source #
(.|.) :: CChar -> CChar -> CChar Source #
xor :: CChar -> CChar -> CChar Source #
complement :: CChar -> CChar Source #
shift :: CChar -> Int -> CChar Source #
rotate :: CChar -> Int -> CChar Source #
setBit :: CChar -> Int -> CChar Source #
clearBit :: CChar -> Int -> CChar Source #
complementBit :: CChar -> Int -> CChar Source #
testBit :: CChar -> Int -> Bool Source #
bitSizeMaybe :: CChar -> Maybe Int Source #
bitSize :: CChar -> Int Source #
isSigned :: CChar -> Bool Source #
shiftL :: CChar -> Int -> CChar Source #
unsafeShiftL :: CChar -> Int -> CChar Source #
shiftR :: CChar -> Int -> CChar Source #
unsafeShiftR :: CChar -> Int -> CChar Source #
rotateL :: CChar -> Int -> CChar Source #
Methods
(.&.) :: Fd -> Fd -> Fd Source #
(.|.) :: Fd -> Fd -> Fd Source #
xor :: Fd -> Fd -> Fd Source #
complement :: Fd -> Fd Source #
shift :: Fd -> Int -> Fd Source #
rotate :: Fd -> Int -> Fd Source #
setBit :: Fd -> Int -> Fd Source #
clearBit :: Fd -> Int -> Fd Source #
complementBit :: Fd -> Int -> Fd Source #
testBit :: Fd -> Int -> Bool Source #
bitSizeMaybe :: Fd -> Maybe Int Source #
isSigned :: Fd -> Bool Source #
shiftL :: Fd -> Int -> Fd Source #
unsafeShiftL :: Fd -> Int -> Fd Source #
shiftR :: Fd -> Int -> Fd Source #
unsafeShiftR :: Fd -> Int -> Fd Source #
rotateL :: Fd -> Int -> Fd Source #
Methods
(.&.) :: CKey -> CKey -> CKey Source #
(.|.) :: CKey -> CKey -> CKey Source #
xor :: CKey -> CKey -> CKey Source #
complement :: CKey -> CKey Source #
shift :: CKey -> Int -> CKey Source #
rotate :: CKey -> Int -> CKey Source #
setBit :: CKey -> Int -> CKey Source #
clearBit :: CKey -> Int -> CKey Source #
complementBit :: CKey -> Int -> CKey Source #
testBit :: CKey -> Int -> Bool Source #
bitSizeMaybe :: CKey -> Maybe Int Source #
bitSize :: CKey -> Int Source #
isSigned :: CKey -> Bool Source #
shiftL :: CKey -> Int -> CKey Source #
unsafeShiftL :: CKey -> Int -> CKey Source #
shiftR :: CKey -> Int -> CKey Source #
unsafeShiftR :: CKey -> Int -> CKey Source #
rotateL :: CKey -> Int -> CKey Source #
Methods
(.&.) :: CId -> CId -> CId Source #
(.|.) :: CId -> CId -> CId Source #
xor :: CId -> CId -> CId Source #
complement :: CId -> CId Source #
shift :: CId -> Int -> CId Source #
rotate :: CId -> Int -> CId Source #
setBit :: CId -> Int -> CId Source #
clearBit :: CId -> Int -> CId Source #
complementBit :: CId -> Int -> CId Source #
testBit :: CId -> Int -> Bool Source #
bitSizeMaybe :: CId -> Maybe Int Source #
bitSize :: CId -> Int Source #
isSigned :: CId -> Bool Source #
shiftL :: CId -> Int -> CId Source #
unsafeShiftL :: CId -> Int -> CId Source #
shiftR :: CId -> Int -> CId Source #
unsafeShiftR :: CId -> Int -> CId Source #
rotateL :: CId -> Int -> CId Source #
Methods
(.&.) :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
(.|.) :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
xor :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt Source #
complement :: CFsFilCnt -> CFsFilCnt Source #
shift :: CFsFilCnt -> Int -> CFsFilCnt Source #
rotate :: CFsFilCnt -> Int -> CFsFilCnt Source #
zeroBits :: CFsFilCnt Source #
bit :: Int -> CFsFilCnt Source #
setBit :: CFsFilCnt -> Int -> CFsFilCnt Source #
clearBit :: CFsFilCnt -> Int -> CFsFilCnt Source #
complementBit :: CFsFilCnt -> Int -> CFsFilCnt Source #
testBit :: CFsFilCnt -> Int -> Bool Source #
bitSizeMaybe :: CFsFilCnt -> Maybe Int Source #
bitSize :: CFsFilCnt -> Int Source #
isSigned :: CFsFilCnt -> Bool Source #
shiftL :: CFsFilCnt -> Int -> CFsFilCnt Source #
unsafeShiftL :: CFsFilCnt -> Int -> CFsFilCnt Source #
shiftR :: CFsFilCnt -> Int -> CFsFilCnt Source #
unsafeShiftR :: CFsFilCnt -> Int -> CFsFilCnt Source #
rotateL :: CFsFilCnt -> Int -> CFsFilCnt Source #
Methods
(.&.) :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
(.|.) :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
xor :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt Source #
complement :: CFsBlkCnt -> CFsBlkCnt Source #
shift :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
rotate :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
zeroBits :: CFsBlkCnt Source #
bit :: Int -> CFsBlkCnt Source #
setBit :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
clearBit :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
complementBit :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
testBit :: CFsBlkCnt -> Int -> Bool Source #
bitSizeMaybe :: CFsBlkCnt -> Maybe Int Source #
bitSize :: CFsBlkCnt -> Int Source #
isSigned :: CFsBlkCnt -> Bool Source #
shiftL :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
unsafeShiftL :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
shiftR :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
unsafeShiftR :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
rotateL :: CFsBlkCnt -> Int -> CFsBlkCnt Source #
Methods
(.&.) :: CClockId -> CClockId -> CClockId Source #
(.|.) :: CClockId -> CClockId -> CClockId Source #
xor :: CClockId -> CClockId -> CClockId Source #
complement :: CClockId -> CClockId Source #
shift :: CClockId -> Int -> CClockId Source #
rotate :: CClockId -> Int -> CClockId Source #
bit :: Int -> CClockId Source #
setBit :: CClockId -> Int -> CClockId Source #
clearBit :: CClockId -> Int -> CClockId Source #
complementBit :: CClockId -> Int -> CClockId Source #
testBit :: CClockId -> Int -> Bool Source #
bitSizeMaybe :: CClockId -> Maybe Int Source #
bitSize :: CClockId -> Int Source #
isSigned :: CClockId -> Bool Source #
shiftL :: CClockId -> Int -> CClockId Source #
unsafeShiftL :: CClockId -> Int -> CClockId Source #
shiftR :: CClockId -> Int -> CClockId Source #
unsafeShiftR :: CClockId -> Int -> CClockId Source #
rotateL :: CClockId -> Int -> CClockId Source #
Methods
(.&.) :: CBlkCnt -> CBlkCnt -> CBlkCnt Source #
(.|.) :: CBlkCnt -> CBlkCnt -> CBlkCnt Source #
xor :: CBlkCnt -> CBlkCnt -> CBlkCnt Source #
complement :: CBlkCnt -> CBlkCnt Source #
shift :: CBlkCnt -> Int -> CBlkCnt Source #
rotate :: CBlkCnt -> Int -> CBlkCnt Source #
bit :: Int -> CBlkCnt Source #
setBit :: CBlkCnt -> Int -> CBlkCnt Source #
clearBit :: CBlkCnt -> Int -> CBlkCnt Source #
complementBit :: CBlkCnt -> Int -> CBlkCnt Source #
testBit :: CBlkCnt -> Int -> Bool Source #
bitSizeMaybe :: CBlkCnt -> Maybe Int Source #
bitSize :: CBlkCnt -> Int Source #
isSigned :: CBlkCnt -> Bool Source #
shiftL :: CBlkCnt -> Int -> CBlkCnt Source #
unsafeShiftL :: CBlkCnt -> Int -> CBlkCnt Source #
shiftR :: CBlkCnt -> Int -> CBlkCnt Source #
unsafeShiftR :: CBlkCnt -> Int -> CBlkCnt Source #
rotateL :: CBlkCnt -> Int -> CBlkCnt Source #
Methods
(.&.) :: CBlkSize -> CBlkSize -> CBlkSize Source #
(.|.) :: CBlkSize -> CBlkSize -> CBlkSize Source #
xor :: CBlkSize -> CBlkSize -> CBlkSize Source #
complement :: CBlkSize -> CBlkSize Source #
shift :: CBlkSize -> Int -> CBlkSize Source #
rotate :: CBlkSize -> Int -> CBlkSize Source #
bit :: Int -> CBlkSize Source #
setBit :: CBlkSize -> Int -> CBlkSize Source #
clearBit :: CBlkSize -> Int -> CBlkSize Source #
complementBit :: CBlkSize -> Int -> CBlkSize Source #
testBit :: CBlkSize -> Int -> Bool Source #
bitSizeMaybe :: CBlkSize -> Maybe Int Source #
bitSize :: CBlkSize -> Int Source #
isSigned :: CBlkSize -> Bool Source #
shiftL :: CBlkSize -> Int -> CBlkSize Source #
unsafeShiftL :: CBlkSize -> Int -> CBlkSize Source #
shiftR :: CBlkSize -> Int -> CBlkSize Source #
unsafeShiftR :: CBlkSize -> Int -> CBlkSize Source #
rotateL :: CBlkSize -> Int -> CBlkSize Source #
Methods
(.&.) :: CRLim -> CRLim -> CRLim Source #
(.|.) :: CRLim -> CRLim -> CRLim Source #
xor :: CRLim -> CRLim -> CRLim Source #
complement :: CRLim -> CRLim Source #
shift :: CRLim -> Int -> CRLim Source #
rotate :: CRLim -> Int -> CRLim Source #
setBit :: CRLim -> Int -> CRLim Source #
clearBit :: CRLim -> Int -> CRLim Source #
complementBit :: CRLim -> Int -> CRLim Source #
testBit :: CRLim -> Int -> Bool Source #
bitSizeMaybe :: CRLim -> Maybe Int Source #
bitSize :: CRLim -> Int Source #
isSigned :: CRLim -> Bool Source #
shiftL :: CRLim -> Int -> CRLim Source #
unsafeShiftL :: CRLim -> Int -> CRLim Source #
shiftR :: CRLim -> Int -> CRLim Source #
unsafeShiftR :: CRLim -> Int -> CRLim Source #
rotateL :: CRLim -> Int -> CRLim Source #
Methods
(.&.) :: CTcflag -> CTcflag -> CTcflag Source #
(.|.) :: CTcflag -> CTcflag -> CTcflag Source #
xor :: CTcflag -> CTcflag -> CTcflag Source #
complement :: CTcflag -> CTcflag Source #
shift :: CTcflag -> Int -> CTcflag Source #
rotate :: CTcflag -> Int -> CTcflag Source #
bit :: Int -> CTcflag Source #
setBit :: CTcflag -> Int -> CTcflag Source #
clearBit :: CTcflag -> Int -> CTcflag Source #
complementBit :: CTcflag -> Int -> CTcflag Source #
testBit :: CTcflag -> Int -> Bool Source #
bitSizeMaybe :: CTcflag -> Maybe Int Source #
bitSize :: CTcflag -> Int Source #
isSigned :: CTcflag -> Bool Source #
shiftL :: CTcflag -> Int -> CTcflag Source #
unsafeShiftL :: CTcflag -> Int -> CTcflag Source #
shiftR :: CTcflag -> Int -> CTcflag Source #
unsafeShiftR :: CTcflag -> Int -> CTcflag Source #
rotateL :: CTcflag -> Int -> CTcflag Source #
Methods
(.&.) :: CUid -> CUid -> CUid Source #
(.|.) :: CUid -> CUid -> CUid Source #
xor :: CUid -> CUid -> CUid Source #
complement :: CUid -> CUid Source #
shift :: CUid -> Int -> CUid Source #
rotate :: CUid -> Int -> CUid Source #
setBit :: CUid -> Int -> CUid Source #
clearBit :: CUid -> Int -> CUid Source #
complementBit :: CUid -> Int -> CUid Source #
testBit :: CUid -> Int -> Bool Source #
bitSizeMaybe :: CUid -> Maybe Int Source #
bitSize :: CUid -> Int Source #
isSigned :: CUid -> Bool Source #
shiftL :: CUid -> Int -> CUid Source #
unsafeShiftL :: CUid -> Int -> CUid Source #
shiftR :: CUid -> Int -> CUid Source #
unsafeShiftR :: CUid -> Int -> CUid Source #
rotateL :: CUid -> Int -> CUid Source #
Methods
(.&.) :: CNlink -> CNlink -> CNlink Source #
(.|.) :: CNlink -> CNlink -> CNlink Source #
xor :: CNlink -> CNlink -> CNlink Source #
complement :: CNlink -> CNlink Source #
shift :: CNlink -> Int -> CNlink Source #
rotate :: CNlink -> Int -> CNlink Source #
setBit :: CNlink -> Int -> CNlink Source #
clearBit :: CNlink -> Int -> CNlink Source #
complementBit :: CNlink -> Int -> CNlink Source #
testBit :: CNlink -> Int -> Bool Source #
bitSizeMaybe :: CNlink -> Maybe Int Source #
bitSize :: CNlink -> Int Source #
isSigned :: CNlink -> Bool Source #
shiftL :: CNlink -> Int -> CNlink Source #
unsafeShiftL :: CNlink -> Int -> CNlink Source #
shiftR :: CNlink -> Int -> CNlink Source #
unsafeShiftR :: CNlink -> Int -> CNlink Source #
rotateL :: CNlink -> Int -> CNlink Source #
Methods
(.&.) :: CGid -> CGid -> CGid Source #
(.|.) :: CGid -> CGid -> CGid Source #
xor :: CGid -> CGid -> CGid Source #
complement :: CGid -> CGid Source #
shift :: CGid -> Int -> CGid Source #
rotate :: CGid -> Int -> CGid Source #
setBit :: CGid -> Int -> CGid Source #
clearBit :: CGid -> Int -> CGid Source #
complementBit :: CGid -> Int -> CGid Source #
testBit :: CGid -> Int -> Bool Source #
bitSizeMaybe :: CGid -> Maybe Int Source #
bitSize :: CGid -> Int Source #
isSigned :: CGid -> Bool Source #
shiftL :: CGid -> Int -> CGid Source #
unsafeShiftL :: CGid -> Int -> CGid Source #
shiftR :: CGid -> Int -> CGid Source #
unsafeShiftR :: CGid -> Int -> CGid Source #
rotateL :: CGid -> Int -> CGid Source #
Methods
(.&.) :: CSsize -> CSsize -> CSsize Source #
(.|.) :: CSsize -> CSsize -> CSsize Source #
xor :: CSsize -> CSsize -> CSsize Source #
complement :: CSsize -> CSsize Source #
shift :: CSsize -> Int -> CSsize Source #
rotate :: CSsize -> Int -> CSsize Source #
setBit :: CSsize -> Int -> CSsize Source #
clearBit :: CSsize -> Int -> CSsize Source #
complementBit :: CSsize -> Int -> CSsize Source #
testBit :: CSsize -> Int -> Bool Source #
bitSizeMaybe :: CSsize -> Maybe Int Source #
bitSize :: CSsize -> Int Source #
isSigned :: CSsize -> Bool Source #
shiftL :: CSsize -> Int -> CSsize Source #
unsafeShiftL :: CSsize -> Int -> CSsize Source #
shiftR :: CSsize -> Int -> CSsize Source #
unsafeShiftR :: CSsize -> Int -> CSsize Source #
rotateL :: CSsize -> Int -> CSsize Source #
Methods
(.&.) :: CPid -> CPid -> CPid Source #
(.|.) :: CPid -> CPid -> CPid Source #
xor :: CPid -> CPid -> CPid Source #
complement :: CPid -> CPid Source #
shift :: CPid -> Int -> CPid Source #
rotate :: CPid -> Int -> CPid Source #
setBit :: CPid -> Int -> CPid Source #
clearBit :: CPid -> Int -> CPid Source #
complementBit :: CPid -> Int -> CPid Source #
testBit :: CPid -> Int -> Bool Source #
bitSizeMaybe :: CPid -> Maybe Int Source #
bitSize :: CPid -> Int Source #
isSigned :: CPid -> Bool Source #
shiftL :: CPid -> Int -> CPid Source #
unsafeShiftL :: CPid -> Int -> CPid Source #
shiftR :: CPid -> Int -> CPid Source #
unsafeShiftR :: CPid -> Int -> CPid Source #
rotateL :: CPid -> Int -> CPid Source #
Methods
(.&.) :: COff -> COff -> COff Source #
(.|.) :: COff -> COff -> COff Source #
xor :: COff -> COff -> COff Source #
complement :: COff -> COff Source #
shift :: COff -> Int -> COff Source #
rotate :: COff -> Int -> COff Source #
setBit :: COff -> Int -> COff Source #
clearBit :: COff -> Int -> COff Source #
complementBit :: COff -> Int -> COff Source #
testBit :: COff -> Int -> Bool Source #
bitSizeMaybe :: COff -> Maybe Int Source #
bitSize :: COff -> Int Source #
isSigned :: COff -> Bool Source #
shiftL :: COff -> Int -> COff Source #
unsafeShiftL :: COff -> Int -> COff Source #
shiftR :: COff -> Int -> COff Source #
unsafeShiftR :: COff -> Int -> COff Source #
rotateL :: COff -> Int -> COff Source #
Methods
(.&.) :: CMode -> CMode -> CMode Source #
(.|.) :: CMode -> CMode -> CMode Source #
xor :: CMode -> CMode -> CMode Source #
complement :: CMode -> CMode Source #
shift :: CMode -> Int -> CMode Source #
rotate :: CMode -> Int -> CMode Source #
setBit :: CMode -> Int -> CMode Source #
clearBit :: CMode -> Int -> CMode Source #
complementBit :: CMode -> Int -> CMode Source #
testBit :: CMode -> Int -> Bool Source #
bitSizeMaybe :: CMode -> Maybe Int Source #
bitSize :: CMode -> Int Source #
isSigned :: CMode -> Bool Source #
shiftL :: CMode -> Int -> CMode Source #
unsafeShiftL :: CMode -> Int -> CMode Source #
shiftR :: CMode -> Int -> CMode Source #
unsafeShiftR :: CMode -> Int -> CMode Source #
rotateL :: CMode -> Int -> CMode Source #
Methods
(.&.) :: CIno -> CIno -> CIno Source #
(.|.) :: CIno -> CIno -> CIno Source #
xor :: CIno -> CIno -> CIno Source #
complement :: CIno -> CIno Source #
shift :: CIno -> Int -> CIno Source #
rotate :: CIno -> Int -> CIno Source #
setBit :: CIno -> Int -> CIno Source #
clearBit :: CIno -> Int -> CIno Source #
complementBit :: CIno -> Int -> CIno Source #
testBit :: CIno -> Int -> Bool Source #
bitSizeMaybe :: CIno -> Maybe Int Source #
bitSize :: CIno -> Int Source #
isSigned :: CIno -> Bool Source #
shiftL :: CIno -> Int -> CIno Source #
unsafeShiftL :: CIno -> Int -> CIno Source #
shiftR :: CIno -> Int -> CIno Source #
unsafeShiftR :: CIno -> Int -> CIno Source #
rotateL :: CIno -> Int -> CIno Source #
Methods
(.&.) :: CDev -> CDev -> CDev Source #
(.|.) :: CDev -> CDev -> CDev Source #
xor :: CDev -> CDev -> CDev Source #
complement :: CDev -> CDev Source #
shift :: CDev -> Int -> CDev Source #
rotate :: CDev -> Int -> CDev Source #
setBit :: CDev -> Int -> CDev Source #
clearBit :: CDev -> Int -> CDev Source #
complementBit :: CDev -> Int -> CDev Source #
testBit :: CDev -> Int -> Bool Source #
bitSizeMaybe :: CDev -> Maybe Int Source #
bitSize :: CDev -> Int Source #
isSigned :: CDev -> Bool Source #
shiftL :: CDev -> Int -> CDev Source #
unsafeShiftL :: CDev -> Int -> CDev Source #
shiftR :: CDev -> Int -> CDev Source #
unsafeShiftR :: CDev -> Int -> CDev Source #
rotateL :: CDev -> Int -> CDev Source #
Methods
(.&.) :: Identity a -> Identity a -> Identity a Source #
(.|.) :: Identity a -> Identity a -> Identity a Source #
xor :: Identity a -> Identity a -> Identity a Source #
complement :: Identity a -> Identity a Source #
shift :: Identity a -> Int -> Identity a Source #
rotate :: Identity a -> Int -> Identity a Source #
zeroBits :: Identity a Source #
bit :: Int -> Identity a Source #
setBit :: Identity a -> Int -> Identity a Source #
clearBit :: Identity a -> Int -> Identity a Source #
complementBit :: Identity a -> Int -> Identity a Source #
testBit :: Identity a -> Int -> Bool Source #
bitSizeMaybe :: Identity a -> Maybe Int Source #
bitSize :: Identity a -> Int Source #
isSigned :: Identity a -> Bool Source #
shiftL :: Identity a -> Int -> Identity a Source #
unsafeShiftL :: Identity a -> Int -> Identity a Source #
shiftR :: Identity a -> Int -> Identity a Source #
unsafeShiftR :: Identity a -> Int -> Identity a Source #
rotateL :: Identity a -> Int -> Identity a Source #
Methods
(.&.) :: Const k a b -> Const k a b -> Const k a b Source #
(.|.) :: Const k a b -> Const k a b -> Const k a b Source #
xor :: Const k a b -> Const k a b -> Const k a b Source #
complement :: Const k a b -> Const k a b Source #
shift :: Const k a b -> Int -> Const k a b Source #
rotate :: Const k a b -> Int -> Const k a b Source #
zeroBits :: Const k a b Source #
bit :: Int -> Const k a b Source #
setBit :: Const k a b -> Int -> Const k a b Source #
clearBit :: Const k a b -> Int -> Const k a b Source #
complementBit :: Const k a b -> Int -> Const k a b Source #
testBit :: Const k a b -> Int -> Bool Source #
bitSizeMaybe :: Const k a b -> Maybe Int Source #
bitSize :: Const k a b -> Int Source #
isSigned :: Const k a b -> Bool Source #
shiftL :: Const k a b -> Int -> Const k a b Source #
unsafeShiftL :: Const k a b -> Int -> Const k a b Source #
shiftR :: Const k a b -> Int -> Const k a b Source #
unsafeShiftR :: Const k a b -> Int -> Const k a b Source #
rotateL :: Const k a b -> Int -> Const k a b 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
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
Methods
finiteBitSize :: Bool -> Int Source #
countLeadingZeros :: Bool -> Int Source #
countTrailingZeros :: Bool -> Int Source #
Methods
finiteBitSize :: Int -> Int Source #
countLeadingZeros :: Int -> Int Source #
countTrailingZeros :: Int -> Int Source #
Methods
finiteBitSize :: Int8 -> Int Source #
countLeadingZeros :: Int8 -> Int Source #
countTrailingZeros :: Int8 -> Int Source #
Methods
finiteBitSize :: Int16 -> Int Source #
countLeadingZeros :: Int16 -> Int Source #
countTrailingZeros :: Int16 -> Int Source #
Methods
finiteBitSize :: Int32 -> Int Source #
countLeadingZeros :: Int32 -> Int Source #
countTrailingZeros :: Int32 -> Int Source #
Methods
finiteBitSize :: Int64 -> Int Source #
countLeadingZeros :: Int64 -> Int Source #
countTrailingZeros :: Int64 -> Int Source #
Methods
finiteBitSize :: Word -> Int Source #
countLeadingZeros :: Word -> Int Source #
countTrailingZeros :: Word -> Int Source #
Methods
finiteBitSize :: Word8 -> Int Source #
countLeadingZeros :: Word8 -> Int Source #
countTrailingZeros :: Word8 -> Int Source #
Methods
finiteBitSize :: Word16 -> Int Source #
countLeadingZeros :: Word16 -> Int Source #
countTrailingZeros :: Word16 -> Int Source #
Methods
finiteBitSize :: Word32 -> Int Source #
countLeadingZeros :: Word32 -> Int Source #
countTrailingZeros :: Word32 -> Int Source #
Methods
finiteBitSize :: Word64 -> Int Source #
countLeadingZeros :: Word64 -> Int Source #
countTrailingZeros :: Word64 -> Int Source #
Methods
finiteBitSize :: IntPtr -> Int Source #
countLeadingZeros :: IntPtr -> Int Source #
countTrailingZeros :: IntPtr -> Int Source #
Methods
finiteBitSize :: WordPtr -> Int Source #
countLeadingZeros :: WordPtr -> Int Source #
countTrailingZeros :: WordPtr -> Int Source #
Methods
finiteBitSize :: CUIntMax -> Int Source #
countLeadingZeros :: CUIntMax -> Int Source #
countTrailingZeros :: CUIntMax -> Int Source #
Methods
finiteBitSize :: CIntMax -> Int Source #
countLeadingZeros :: CIntMax -> Int Source #
countTrailingZeros :: CIntMax -> Int Source #
Methods
finiteBitSize :: CUIntPtr -> Int Source #
countLeadingZeros :: CUIntPtr -> Int Source #
countTrailingZeros :: CUIntPtr -> Int Source #
Methods
finiteBitSize :: CIntPtr -> Int Source #
countLeadingZeros :: CIntPtr -> Int Source #
countTrailingZeros :: CIntPtr -> Int Source #
Methods
finiteBitSize :: CSigAtomic -> Int Source #
countLeadingZeros :: CSigAtomic -> Int Source #
countTrailingZeros :: CSigAtomic -> Int Source #
Methods
finiteBitSize :: CWchar -> Int Source #
countLeadingZeros :: CWchar -> Int Source #
countTrailingZeros :: CWchar -> Int Source #
Methods
finiteBitSize :: CSize -> Int Source #
countLeadingZeros :: CSize -> Int Source #
countTrailingZeros :: CSize -> Int Source #
Methods
finiteBitSize :: CPtrdiff -> Int Source #
countLeadingZeros :: CPtrdiff -> Int Source #
countTrailingZeros :: CPtrdiff -> Int Source #
Methods
finiteBitSize :: CBool -> Int Source #
countLeadingZeros :: CBool -> Int Source #
countTrailingZeros :: CBool -> Int Source #
Methods
finiteBitSize :: CULLong -> Int Source #
countLeadingZeros :: CULLong -> Int Source #
countTrailingZeros :: CULLong -> Int Source #
Methods
finiteBitSize :: CLLong -> Int Source #
countLeadingZeros :: CLLong -> Int Source #
countTrailingZeros :: CLLong -> Int Source #
Methods
finiteBitSize :: CULong -> Int Source #
countLeadingZeros :: CULong -> Int Source #
countTrailingZeros :: CULong -> Int Source #
Methods
finiteBitSize :: CLong -> Int Source #
countLeadingZeros :: CLong -> Int Source #
countTrailingZeros :: CLong -> Int Source #
Methods
finiteBitSize :: CUInt -> Int Source #
countLeadingZeros :: CUInt -> Int Source #
countTrailingZeros :: CUInt -> Int Source #
Methods
finiteBitSize :: CInt -> Int Source #
countLeadingZeros :: CInt -> Int Source #
countTrailingZeros :: CInt -> Int Source #
Methods
finiteBitSize :: CUShort -> Int Source #
countLeadingZeros :: CUShort -> Int Source #
countTrailingZeros :: CUShort -> Int Source #
Methods
finiteBitSize :: CShort -> Int Source #
countLeadingZeros :: CShort -> Int Source #
countTrailingZeros :: CShort -> Int Source #
Methods
finiteBitSize :: CUChar -> Int Source #
countLeadingZeros :: CUChar -> Int Source #
countTrailingZeros :: CUChar -> Int Source #
Methods
finiteBitSize :: CSChar -> Int Source #
countLeadingZeros :: CSChar -> Int Source #
countTrailingZeros :: CSChar -> Int Source #
Methods
finiteBitSize :: CChar -> Int Source #
countLeadingZeros :: CChar -> Int Source #
countTrailingZeros :: CChar -> Int Source #
Methods
finiteBitSize :: Fd -> Int Source #
countLeadingZeros :: Fd -> Int Source #
countTrailingZeros :: Fd -> Int Source #
Methods
finiteBitSize :: CKey -> Int Source #
countLeadingZeros :: CKey -> Int Source #
countTrailingZeros :: CKey -> Int Source #
Methods
finiteBitSize :: CId -> Int Source #
countLeadingZeros :: CId -> Int Source #
countTrailingZeros :: CId -> Int Source #
Methods
finiteBitSize :: CFsFilCnt -> Int Source #
countLeadingZeros :: CFsFilCnt -> Int Source #
countTrailingZeros :: CFsFilCnt -> Int Source #
Methods
finiteBitSize :: CFsBlkCnt -> Int Source #
countLeadingZeros :: CFsBlkCnt -> Int Source #
countTrailingZeros :: CFsBlkCnt -> Int Source #
Methods
finiteBitSize :: CClockId -> Int Source #
countLeadingZeros :: CClockId -> Int Source #
countTrailingZeros :: CClockId -> Int Source #
Methods
finiteBitSize :: CBlkCnt -> Int Source #
countLeadingZeros :: CBlkCnt -> Int Source #
countTrailingZeros :: CBlkCnt -> Int Source #
Methods
finiteBitSize :: CBlkSize -> Int Source #
countLeadingZeros :: CBlkSize -> Int Source #
countTrailingZeros :: CBlkSize -> Int Source #
Methods
finiteBitSize :: CRLim -> Int Source #
countLeadingZeros :: CRLim -> Int Source #
countTrailingZeros :: CRLim -> Int Source #
Methods
finiteBitSize :: CTcflag -> Int Source #
countLeadingZeros :: CTcflag -> Int Source #
countTrailingZeros :: CTcflag -> Int Source #
Methods
finiteBitSize :: CUid -> Int Source #
countLeadingZeros :: CUid -> Int Source #
countTrailingZeros :: CUid -> Int Source #
Methods
finiteBitSize :: CNlink -> Int Source #
countLeadingZeros :: CNlink -> Int Source #
countTrailingZeros :: CNlink -> Int Source #
Methods
finiteBitSize :: CGid -> Int Source #
countLeadingZeros :: CGid -> Int Source #
countTrailingZeros :: CGid -> Int Source #
Methods
finiteBitSize :: CSsize -> Int Source #
countLeadingZeros :: CSsize -> Int Source #
countTrailingZeros :: CSsize -> Int Source #
Methods
finiteBitSize :: CPid -> Int Source #
countLeadingZeros :: CPid -> Int Source #
countTrailingZeros :: CPid -> Int Source #
Methods
finiteBitSize :: COff -> Int Source #
countLeadingZeros :: COff -> Int Source #
countTrailingZeros :: COff -> Int Source #
Methods
finiteBitSize :: CMode -> Int Source #
countLeadingZeros :: CMode -> Int Source #
countTrailingZeros :: CMode -> Int Source #
Methods
finiteBitSize :: CIno -> Int Source #
countLeadingZeros :: CIno -> Int Source #
countTrailingZeros :: CIno -> Int Source #
Methods
finiteBitSize :: CDev -> Int Source #
countLeadingZeros :: CDev -> Int Source #
countTrailingZeros :: CDev -> Int Source #
Methods
finiteBitSize :: Identity a -> Int Source #
countLeadingZeros :: Identity a -> Int Source #
countTrailingZeros :: Identity a -> Int Source #
Methods
finiteBitSize :: Const k a b -> Int Source #
countLeadingZeros :: Const k a b -> Int Source #
countTrailingZeros :: Const k a b -> Int Source #
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