base-4.17.0.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
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

Type classes

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 #

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: base-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 #

x `testBit` i is the same as x .&. bit n /= 0

In other words it returns True if the bit at offset @n is set.

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: base-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 .

Default implementation based upon bitSizeMaybe provided since 4.12.0.0.

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). Some instances may throw an Overflow exception if given a negative input.

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: base-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 . Some instances may throw an Overflow exception if given a negative input.

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: base-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: base-4.5.0.0

Instances

Instances details
Bits Int16 Source #

Since: base-2.1

Bits Int32 Source #

Since: base-2.1

Bits Int64 Source #

Since: base-2.1

Bits Int8 Source #

Since: base-2.1

Bits Word16 Source #

Since: base-2.1

Bits Word32 Source #

Since: base-2.1

Bits Word64 Source #

Since: base-2.1

Bits Word8 Source #

Since: base-2.1

Instance details

Defined in System.Posix.Types

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 #

zeroBits :: Fd Source #

bit :: 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 #

bitSize :: Fd -> 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 #

rotateR :: Fd -> Int -> Fd Source #

popCount :: Fd -> Int Source #

Bits Integer Source #

Since: base-2.1

Bits Natural Source #

Since: base-4.8.0

Bits Bool Source #

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Bits Int Source #

Since: base-2.1

Bits Word Source #

Since: base-2.1

Bits a => Bits (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: And a -> And a -> And a Source #

(.|.) :: And a -> And a -> And a Source #

xor :: And a -> And a -> And a Source #

complement :: And a -> And a Source #

shift :: And a -> Int -> And a Source #

rotate :: And a -> Int -> And a Source #

zeroBits :: And a Source #

bit :: Int -> And a Source #

setBit :: And a -> Int -> And a Source #

clearBit :: And a -> Int -> And a Source #

complementBit :: And a -> Int -> And a Source #

testBit :: And a -> Int -> Bool Source #

bitSizeMaybe :: And a -> Maybe Int Source #

bitSize :: And a -> Int Source #

isSigned :: And a -> Bool Source #

shiftL :: And a -> Int -> And a Source #

unsafeShiftL :: And a -> Int -> And a Source #

shiftR :: And a -> Int -> And a Source #

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

rotateL :: And a -> Int -> And a Source #

rotateR :: And a -> Int -> And a Source #

popCount :: And a -> Int Source #

Bits a => Bits (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Iff a -> Iff a -> Iff a Source #

(.|.) :: Iff a -> Iff a -> Iff a Source #

xor :: Iff a -> Iff a -> Iff a Source #

complement :: Iff a -> Iff a Source #

shift :: Iff a -> Int -> Iff a Source #

rotate :: Iff a -> Int -> Iff a Source #

zeroBits :: Iff a Source #

bit :: Int -> Iff a Source #

setBit :: Iff a -> Int -> Iff a Source #

clearBit :: Iff a -> Int -> Iff a Source #

complementBit :: Iff a -> Int -> Iff a Source #

testBit :: Iff a -> Int -> Bool Source #

bitSizeMaybe :: Iff a -> Maybe Int Source #

bitSize :: Iff a -> Int Source #

isSigned :: Iff a -> Bool Source #

shiftL :: Iff a -> Int -> Iff a Source #

unsafeShiftL :: Iff a -> Int -> Iff a Source #

shiftR :: Iff a -> Int -> Iff a Source #

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

rotateL :: Iff a -> Int -> Iff a Source #

rotateR :: Iff a -> Int -> Iff a Source #

popCount :: Iff a -> Int Source #

Bits a => Bits (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Ior a -> Ior a -> Ior a Source #

(.|.) :: Ior a -> Ior a -> Ior a Source #

xor :: Ior a -> Ior a -> Ior a Source #

complement :: Ior a -> Ior a Source #

shift :: Ior a -> Int -> Ior a Source #

rotate :: Ior a -> Int -> Ior a Source #

zeroBits :: Ior a Source #

bit :: Int -> Ior a Source #

setBit :: Ior a -> Int -> Ior a Source #

clearBit :: Ior a -> Int -> Ior a Source #

complementBit :: Ior a -> Int -> Ior a Source #

testBit :: Ior a -> Int -> Bool Source #

bitSizeMaybe :: Ior a -> Maybe Int Source #

bitSize :: Ior a -> Int Source #

isSigned :: Ior a -> Bool Source #

shiftL :: Ior a -> Int -> Ior a Source #

unsafeShiftL :: Ior a -> Int -> Ior a Source #

shiftR :: Ior a -> Int -> Ior a Source #

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

rotateL :: Ior a -> Int -> Ior a Source #

rotateR :: Ior a -> Int -> Ior a Source #

popCount :: Ior a -> Int Source #

Bits a => Bits (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Xor a -> Xor a -> Xor a Source #

(.|.) :: Xor a -> Xor a -> Xor a Source #

xor :: Xor a -> Xor a -> Xor a Source #

complement :: Xor a -> Xor a Source #

shift :: Xor a -> Int -> Xor a Source #

rotate :: Xor a -> Int -> Xor a Source #

zeroBits :: Xor a Source #

bit :: Int -> Xor a Source #

setBit :: Xor a -> Int -> Xor a Source #

clearBit :: Xor a -> Int -> Xor a Source #

complementBit :: Xor a -> Int -> Xor a Source #

testBit :: Xor a -> Int -> Bool Source #

bitSizeMaybe :: Xor a -> Maybe Int Source #

bitSize :: Xor a -> Int Source #

isSigned :: Xor a -> Bool Source #

shiftL :: Xor a -> Int -> Xor a Source #

unsafeShiftL :: Xor a -> Int -> Xor a Source #

shiftR :: Xor a -> Int -> Xor a Source #

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

rotateL :: Xor a -> Int -> Xor a Source #

rotateR :: Xor a -> Int -> Xor a Source #

popCount :: Xor a -> Int Source #

Bits a => Bits (Identity a) Source #

Since: base-4.9.0.0

Bits a => Bits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(.&.) :: Down a -> Down a -> Down a Source #

(.|.) :: Down a -> Down a -> Down a Source #

xor :: Down a -> Down a -> Down a Source #

complement :: Down a -> Down a Source #

shift :: Down a -> Int -> Down a Source #

rotate :: Down a -> Int -> Down a Source #

zeroBits :: Down a Source #

bit :: Int -> Down a Source #

setBit :: Down a -> Int -> Down a Source #

clearBit :: Down a -> Int -> Down a Source #

complementBit :: Down a -> Int -> Down a Source #

testBit :: Down a -> Int -> Bool Source #

bitSizeMaybe :: Down a -> Maybe Int Source #

bitSize :: Down a -> Int Source #

isSigned :: Down a -> Bool Source #

shiftL :: Down a -> Int -> Down a Source #

unsafeShiftL :: Down a -> Int -> Down a Source #

shiftR :: Down a -> Int -> Down a Source #

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

rotateL :: Down a -> Int -> Down a Source #

rotateR :: Down a -> Int -> Down a Source #

popCount :: Down a -> Int Source #

Bits a => Bits (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

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: base-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: base-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: base-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: base-4.8.0.0

Instances

Instances details
FiniteBits Int16 Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBits Int32 Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBits Int64 Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBits Int8 Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBits Word16 Source #

Since: base-4.6.0.0

FiniteBits Word32 Source #

Since: base-4.6.0.0

FiniteBits Word64 Source #

Since: base-4.6.0.0

FiniteBits Word8 Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Instance details

Defined in System.Posix.Types

FiniteBits Bool Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Bits

FiniteBits Int Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

FiniteBits Word Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

FiniteBits a => FiniteBits (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

FiniteBits a => FiniteBits (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

FiniteBits a => FiniteBits (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

FiniteBits a => FiniteBits (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

FiniteBits a => FiniteBits (Identity a) Source #

Since: base-4.9.0.0

FiniteBits a => FiniteBits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

FiniteBits a => FiniteBits (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Extra functions

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

Default implementation for bit .

Note that: bitDefault i = 1 shiftL i

Since: base-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: base-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: base-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 == toInteger y = Just y
 | otherwise = Nothing
 where
 y = fromIntegral 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: base-4.8.0.0

oneBits :: FiniteBits a => a Source #

A more concise version of complement zeroBits.

>>> complement (zeroBits :: Word) == (oneBits :: Word)
True
>>> complement (oneBits :: Word) == (zeroBits :: Word)
True

Note

The constraint on oneBits is arguably too strong. However, as some types (such as Natural) have undefined complement , this is the only safe choice.

Since: base-4.16

(.^.) :: Bits a => a -> a -> a infixl 6 Source #

Infix version of xor .

Since: base-4.17

(.>>.) :: Bits a => a -> Int -> a infixl 8 Source #

Infix version of shiftR .

Since: base-4.17

(.<<.) :: Bits a => a -> Int -> a infixl 8 Source #

Infix version of shiftL .

Since: base-4.17

(!>>.) :: Bits a => a -> Int -> a infixl 8 Source #

Infix version of unsafeShiftR .

Since: base-4.17

(!<<.) :: Bits a => a -> Int -> a infixl 8 Source #

Infix version of unsafeShiftL .

Since: base-4.17

Newtypes

newtype And a Source #

Monoid under bitwise AND.

>>> getAnd (And 0xab <> And 0x12) :: Word8
2

Since: base-4.16

Constructors

And

Fields

Instances

Instances details
FiniteBits a => Monoid (And a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement , this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: And a Source #

mappend :: And a -> And a -> And a Source #

mconcat :: [And a] -> And a Source #

Bits a => Semigroup (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: And a -> And a -> And a Source #

sconcat :: NonEmpty (And a) -> And a Source #

stimes :: Integral b => b -> And a -> And a Source #

Bits a => Bits (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: And a -> And a -> And a Source #

(.|.) :: And a -> And a -> And a Source #

xor :: And a -> And a -> And a Source #

complement :: And a -> And a Source #

shift :: And a -> Int -> And a Source #

rotate :: And a -> Int -> And a Source #

zeroBits :: And a Source #

bit :: Int -> And a Source #

setBit :: And a -> Int -> And a Source #

clearBit :: And a -> Int -> And a Source #

complementBit :: And a -> Int -> And a Source #

testBit :: And a -> Int -> Bool Source #

bitSizeMaybe :: And a -> Maybe Int Source #

bitSize :: And a -> Int Source #

isSigned :: And a -> Bool Source #

shiftL :: And a -> Int -> And a Source #

unsafeShiftL :: And a -> Int -> And a Source #

shiftR :: And a -> Int -> And a Source #

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

rotateL :: And a -> Int -> And a Source #

rotateR :: And a -> Int -> And a Source #

popCount :: And a -> Int Source #

FiniteBits a => FiniteBits (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Bounded a => Bounded (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

minBound :: And a Source #

maxBound :: And a Source #

Enum a => Enum (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

succ :: And a -> And a Source #

pred :: And a -> And a Source #

toEnum :: Int -> And a Source #

fromEnum :: And a -> Int Source #

enumFrom :: And a -> [And a] Source #

enumFromThen :: And a -> And a -> [And a] Source #

enumFromTo :: And a -> And a -> [And a] Source #

enumFromThenTo :: And a -> And a -> And a -> [And a] Source #

Read a => Read (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Show a => Show (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

showsPrec :: Int -> And a -> ShowS Source #

show :: And a -> String Source #

showList :: [And a] -> ShowS Source #

Eq a => Eq (And a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(==) :: And a -> And a -> Bool Source #

(/=) :: And a -> And a -> Bool Source #

newtype Ior a Source #

Monoid under bitwise inclusive OR.

>>> getIor (Ior 0xab <> Ior 0x12) :: Word8
187

Since: base-4.16

Constructors

Ior

Fields

Instances

Instances details
Bits a => Monoid (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Ior a Source #

mappend :: Ior a -> Ior a -> Ior a Source #

mconcat :: [Ior a] -> Ior a Source #

Bits a => Semigroup (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Ior a -> Ior a -> Ior a Source #

sconcat :: NonEmpty (Ior a) -> Ior a Source #

stimes :: Integral b => b -> Ior a -> Ior a Source #

Bits a => Bits (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Ior a -> Ior a -> Ior a Source #

(.|.) :: Ior a -> Ior a -> Ior a Source #

xor :: Ior a -> Ior a -> Ior a Source #

complement :: Ior a -> Ior a Source #

shift :: Ior a -> Int -> Ior a Source #

rotate :: Ior a -> Int -> Ior a Source #

zeroBits :: Ior a Source #

bit :: Int -> Ior a Source #

setBit :: Ior a -> Int -> Ior a Source #

clearBit :: Ior a -> Int -> Ior a Source #

complementBit :: Ior a -> Int -> Ior a Source #

testBit :: Ior a -> Int -> Bool Source #

bitSizeMaybe :: Ior a -> Maybe Int Source #

bitSize :: Ior a -> Int Source #

isSigned :: Ior a -> Bool Source #

shiftL :: Ior a -> Int -> Ior a Source #

unsafeShiftL :: Ior a -> Int -> Ior a Source #

shiftR :: Ior a -> Int -> Ior a Source #

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

rotateL :: Ior a -> Int -> Ior a Source #

rotateR :: Ior a -> Int -> Ior a Source #

popCount :: Ior a -> Int Source #

FiniteBits a => FiniteBits (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Bounded a => Bounded (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

minBound :: Ior a Source #

maxBound :: Ior a Source #

Enum a => Enum (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

succ :: Ior a -> Ior a Source #

pred :: Ior a -> Ior a Source #

toEnum :: Int -> Ior a Source #

fromEnum :: Ior a -> Int Source #

enumFrom :: Ior a -> [Ior a] Source #

enumFromThen :: Ior a -> Ior a -> [Ior a] Source #

enumFromTo :: Ior a -> Ior a -> [Ior a] Source #

enumFromThenTo :: Ior a -> Ior a -> Ior a -> [Ior a] Source #

Read a => Read (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Show a => Show (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

showsPrec :: Int -> Ior a -> ShowS Source #

show :: Ior a -> String Source #

showList :: [Ior a] -> ShowS Source #

Eq a => Eq (Ior a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(==) :: Ior a -> Ior a -> Bool Source #

(/=) :: Ior a -> Ior a -> Bool Source #

newtype Xor a Source #

Monoid under bitwise XOR.

>>> getXor (Xor 0xab <> Xor 0x12) :: Word8
185

Since: base-4.16

Constructors

Xor

Fields

Instances

Instances details
Bits a => Monoid (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Xor a Source #

mappend :: Xor a -> Xor a -> Xor a Source #

mconcat :: [Xor a] -> Xor a Source #

Bits a => Semigroup (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Xor a -> Xor a -> Xor a Source #

sconcat :: NonEmpty (Xor a) -> Xor a Source #

stimes :: Integral b => b -> Xor a -> Xor a Source #

Bits a => Bits (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Xor a -> Xor a -> Xor a Source #

(.|.) :: Xor a -> Xor a -> Xor a Source #

xor :: Xor a -> Xor a -> Xor a Source #

complement :: Xor a -> Xor a Source #

shift :: Xor a -> Int -> Xor a Source #

rotate :: Xor a -> Int -> Xor a Source #

zeroBits :: Xor a Source #

bit :: Int -> Xor a Source #

setBit :: Xor a -> Int -> Xor a Source #

clearBit :: Xor a -> Int -> Xor a Source #

complementBit :: Xor a -> Int -> Xor a Source #

testBit :: Xor a -> Int -> Bool Source #

bitSizeMaybe :: Xor a -> Maybe Int Source #

bitSize :: Xor a -> Int Source #

isSigned :: Xor a -> Bool Source #

shiftL :: Xor a -> Int -> Xor a Source #

unsafeShiftL :: Xor a -> Int -> Xor a Source #

shiftR :: Xor a -> Int -> Xor a Source #

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

rotateL :: Xor a -> Int -> Xor a Source #

rotateR :: Xor a -> Int -> Xor a Source #

popCount :: Xor a -> Int Source #

FiniteBits a => FiniteBits (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Bounded a => Bounded (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

minBound :: Xor a Source #

maxBound :: Xor a Source #

Enum a => Enum (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

succ :: Xor a -> Xor a Source #

pred :: Xor a -> Xor a Source #

toEnum :: Int -> Xor a Source #

fromEnum :: Xor a -> Int Source #

enumFrom :: Xor a -> [Xor a] Source #

enumFromThen :: Xor a -> Xor a -> [Xor a] Source #

enumFromTo :: Xor a -> Xor a -> [Xor a] Source #

enumFromThenTo :: Xor a -> Xor a -> Xor a -> [Xor a] Source #

Read a => Read (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Show a => Show (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

showsPrec :: Int -> Xor a -> ShowS Source #

show :: Xor a -> String Source #

showList :: [Xor a] -> ShowS Source #

Eq a => Eq (Xor a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(==) :: Xor a -> Xor a -> Bool Source #

(/=) :: Xor a -> Xor a -> Bool Source #

newtype Iff a Source #

Monoid under bitwise 'equality'; defined as 1 if the corresponding bits match, and 0 otherwise.

>>> getIff (Iff 0xab <> Iff 0x12) :: Word8
70

Since: base-4.16

Constructors

Iff

Fields

Instances

Instances details
FiniteBits a => Monoid (Iff a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement , this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Iff a Source #

mappend :: Iff a -> Iff a -> Iff a Source #

mconcat :: [Iff a] -> Iff a Source #

FiniteBits a => Semigroup (Iff a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement , this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(<>) :: Iff a -> Iff a -> Iff a Source #

sconcat :: NonEmpty (Iff a) -> Iff a Source #

stimes :: Integral b => b -> Iff a -> Iff a Source #

Bits a => Bits (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(.&.) :: Iff a -> Iff a -> Iff a Source #

(.|.) :: Iff a -> Iff a -> Iff a Source #

xor :: Iff a -> Iff a -> Iff a Source #

complement :: Iff a -> Iff a Source #

shift :: Iff a -> Int -> Iff a Source #

rotate :: Iff a -> Int -> Iff a Source #

zeroBits :: Iff a Source #

bit :: Int -> Iff a Source #

setBit :: Iff a -> Int -> Iff a Source #

clearBit :: Iff a -> Int -> Iff a Source #

complementBit :: Iff a -> Int -> Iff a Source #

testBit :: Iff a -> Int -> Bool Source #

bitSizeMaybe :: Iff a -> Maybe Int Source #

bitSize :: Iff a -> Int Source #

isSigned :: Iff a -> Bool Source #

shiftL :: Iff a -> Int -> Iff a Source #

unsafeShiftL :: Iff a -> Int -> Iff a Source #

shiftR :: Iff a -> Int -> Iff a Source #

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

rotateL :: Iff a -> Int -> Iff a Source #

rotateR :: Iff a -> Int -> Iff a Source #

popCount :: Iff a -> Int Source #

FiniteBits a => FiniteBits (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Bounded a => Bounded (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

minBound :: Iff a Source #

maxBound :: Iff a Source #

Enum a => Enum (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

succ :: Iff a -> Iff a Source #

pred :: Iff a -> Iff a Source #

toEnum :: Int -> Iff a Source #

fromEnum :: Iff a -> Int Source #

enumFrom :: Iff a -> [Iff a] Source #

enumFromThen :: Iff a -> Iff a -> [Iff a] Source #

enumFromTo :: Iff a -> Iff a -> [Iff a] Source #

enumFromThenTo :: Iff a -> Iff a -> Iff a -> [Iff a] Source #

Read a => Read (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Show a => Show (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

showsPrec :: Int -> Iff a -> ShowS Source #

show :: Iff a -> String Source #

showList :: [Iff a] -> ShowS Source #

Eq a => Eq (Iff a) Source #

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

(==) :: Iff a -> Iff a -> Bool Source #

(/=) :: Iff a -> Iff a -> Bool Source #

AltStyle によって変換されたページ (->オリジナル) /