Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- module Data.Bits
- bitDefault :: (Bits a, Num a) => Int -> a
- testBitDefault :: (Bits a, Num a) => a -> Int -> Bool
- popCountDefault :: (Bits a, Num a) => a -> Int
- (.^.) :: Bits a => a -> a -> a
- (.>>.) :: Bits a => a -> Int -> a
- (.<<.) :: Bits a => a -> Int -> a
- (!>>.) :: Bits a => a -> Int -> a
- (!<<.) :: Bits a => a -> Int -> a
- toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b
- oneBits :: FiniteBits a => a
Documentation
module Data.Bits
bitDefault :: (Bits a, Num a) => Int -> a #
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 -> Int -> a infixl 8 #
Infix version of unsafeShiftR
.
Since: base-4.17
(!<<.) :: Bits a => a -> Int -> a infixl 8 #
Infix version of unsafeShiftL
.
Since: base-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 == 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 #
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