base-compat-0.12.2: A compatibility layer for base
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bits.Compat

Synopsis

Documentation

module Data.Bits

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

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 #

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 #

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

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

Infix version of xor.

Since: 4.17

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

Infix version of shiftR.

Since: 4.17

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

Infix version of shiftL.

Since: 4.17

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

Infix version of unsafeShiftR.

Since: 4.17

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

Infix version of unsafeShiftL.

Since: 4.17

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

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: 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: 4.16