Copyright | (c) 2019 Andrew Lelechenko 2012-2016 James Cook |
---|---|
License | BSD3 |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
This module exposes an interface with thread-safe writes and flips. Consider using Data.Bit, which is faster (up to 20%), but thread-unsafe.
Synopsis
- newtype Bit = Bit {}
- unsafeFlipBit :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m ()
- flipBit :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m ()
- castFromWords :: Vector Word -> Vector Bit
- castToWords :: Vector Bit -> Maybe (Vector Word)
- cloneToWords :: Vector Bit -> Vector Word
- castFromWords8 :: Vector Word8 -> Vector Bit
- castToWords8 :: Vector Bit -> Maybe (Vector Word8)
- cloneToWords8 :: Vector Bit -> Vector Word8
- zipBits :: (forall a. Bits a => a -> a -> a) -> Vector Bit -> Vector Bit -> Vector Bit
- invertBits :: Vector Bit -> Vector Bit
- reverseBits :: Vector Bit -> Vector Bit
- bitIndex :: Bit -> Vector Bit -> Maybe Int
- nthBitIndex :: Bit -> Int -> Vector Bit -> Maybe Int
- countBits :: Vector Bit -> Int
- listBits :: Vector Bit -> [Int]
- selectBits :: Vector Bit -> Vector Bit -> Vector Bit
- excludeBits :: Vector Bit -> Vector Bit -> Vector Bit
- castFromWordsM :: MVector s Word -> MVector s Bit
- castToWordsM :: MVector s Bit -> Maybe (MVector s Word)
- cloneToWordsM :: PrimMonad m => MVector (PrimState m) Bit -> m (MVector (PrimState m) Word)
- zipInPlace :: forall m. PrimMonad m => (forall a. Bits a => a -> a -> a) -> Vector Bit -> MVector (PrimState m) Bit -> m ()
- invertInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m ()
- reverseInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m ()
- selectBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int
- excludeBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int
- data F2Poly
- unF2Poly :: F2Poly -> Vector Bit
- toF2Poly :: Vector Bit -> F2Poly
- gcdExt :: F2Poly -> F2Poly -> (F2Poly, F2Poly)
Documentation
A newtype wrapper with a custom instance
of Data.Vector.Unboxed, which packs booleans
as efficient as possible (8 values per byte).
Vectors of Bit
use 8x less memory
than vectors of Bool
(which stores one value per byte).
but random writes are up to 20% slower.
Instances
unsafeFlipBit :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m () Source #
Flip the bit at the given position.
No bounds checks are performed.
Equivalent to flip
unsafeModify
complement
,
but up to 33% faster and atomic.
In general there is no reason to unsafeModify
bit vectors:
either you modify it with id
(which is id
altogether)
or with complement
(which is unsafeFlipBit
).
>>>
Data.Vector.Unboxed.modify (\v -> unsafeFlipBit v 1) (read "[1,1,1]")
[1,0,1]
flipBit :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m () Source #
Flip the bit at the given position.
Equivalent to flip
modify
complement
,
but up to 33% faster and atomic.
In general there is no reason to modify
bit vectors:
either you modify it with id
(which is id
altogether)
or with complement
(which is flipBit
).
>>>
Data.Vector.Unboxed.modify (\v -> flipBit v 1) (read "[1,1,1]")
[1,0,1]
Immutable conversions
castFromWords :: Vector Word -> Vector Bit Source #
Cast an unboxed vector of words
to an unboxed vector of bits.
Cf. castFromWordsM
.
>>>
castFromWords (Data.Vector.Unboxed.singleton 123)
[1,1,0,1,1,1,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]
castToWords :: Vector Bit -> Maybe (Vector Word) Source #
Try to cast an unboxed vector of bits
to an unboxed vector of words.
It succeeds if a vector of bits is aligned.
Use cloneToWords
otherwise.
Cf. castToWordsM
.
castToWords (castFromWords v) == Just v
cloneToWords :: Vector Bit -> Vector Word Source #
Clone an unboxed vector of bits
to a new unboxed vector of words.
If the bits don't completely fill the words,
the last word will be zero-padded.
Cf. cloneToWordsM
.
>>>
cloneToWords (read "[1,1,0,1,1,1,1,0]")
[123]
castFromWords8 :: Vector Word8 -> Vector Bit Source #
Cast a unboxed vector of Word8
to an unboxed vector of bits.
This can be used in conjunction
with bytestring-to-vector
package
to convert from ByteString
:
>>>
:set -XOverloadedStrings
>>>
import Data.Vector.Storable.ByteString
>>>
castFromWords8 (Data.Vector.convert (byteStringToVector "abc"))
[1,0,0,0,0,1,1,0,0,1,0,0,0,1,1,0,1,1,0,0,0,1,1,0]
castToWords8 :: Vector Bit -> Maybe (Vector Word8) Source #
Try to cast an unboxed vector of bits
to an unboxed vector of Word8
.
It succeeds if a vector of bits is aligned.
Use cloneToWords8
otherwise.
castToWords8 (castFromWords8 v) == Just v
cloneToWords8 :: Vector Bit -> Vector Word8 Source #
Clone an unboxed vector of bits
to a new unboxed vector of Word8
.
If the bits don't completely fill the words,
the last Word8
will be zero-padded.
This can be used in conjunction
with bytestring-to-vector
package
to convert to ByteString
:
>>>
:set -XOverloadedLists
>>>
import Data.Vector.Storable.ByteString
>>>
vectorToByteString (Data.Vector.convert (Data.Bit.cloneToWords8 [1,0,0,0,0,1,1,0,0,1,0,0,0,1,1,0,1,1,0,0,0,1]))
"ab#"
Immutable operations
zipBits :: (forall a. Bits a => a -> a -> a) -> Vector Bit -> Vector Bit -> Vector Bit Source #
Zip two vectors with the given function.
Similar to zipWith
,
but up to 1000x (!) faster.
For sufficiently dense sets, represented as bitmaps,
zipBits
is up to 32x faster than
union
, intersection
, etc.
>>>
import Data.Bits
>>>
zipBits (.&.) (read "[1,1,0]") (read "[0,1,1]") -- intersection
[0,1,0]>>>
zipBits (.|.) (read "[1,1,0]") (read "[0,1,1]") -- union
[1,1,1]>>>
zipBits (\x y -> x .&. complement y) (read "[1,1,0]") (read "[0,1,1]") -- difference
[1,0,0]>>>
zipBits xor (read "[1,1,0]") (read "[0,1,1]") -- symmetric difference
[1,0,1]
invertBits :: Vector Bit -> Vector Bit Source #
Invert (flip) all bits.
>>>
invertBits (read "[0,1,0,1,0]")
[1,0,1,0,1]
reverseBits :: Vector Bit -> Vector Bit Source #
Reverse the order of bits.
>>>
reverseBits (read "[1,1,0,1,0]")
[0,1,0,1,1]
Consider using vector-rotcev
package
to reverse vectors in O(1) time.
bitIndex :: Bit -> Vector Bit -> Maybe Int Source #
Return the index of the first bit in the vector
with the specified value, if any.
Similar to elemIndex
, but up to 64x faster.
>>>
bitIndex (Bit True) (read "[0,0,1,0,1]")
Just 2>>>
bitIndex (Bit True) (read "[0,0,0,0,0]")
Nothing
bitIndex bit == nthBitIndex bit 1
One can also use it to reduce a vector with disjunction or conjunction:
>>>
import Data.Maybe
>>>
isAnyBitSet = isJust . bitIndex (Bit True)
>>>
areAllBitsSet = isNothing . bitIndex (Bit False)
nthBitIndex :: Bit -> Int -> Vector Bit -> Maybe Int Source #
Return the index of the n
-th bit in the vector
with the specified value, if any.
Here n
is 1-based and the index is 0-based.
Non-positive n
results in an error.
>>>
nthBitIndex (Bit True) 2 (read "[0,1,0,1,1,1,0]")
Just 3>>>
nthBitIndex (Bit True) 5 (read "[0,1,0,1,1,1,0]")
Nothing
One can use nthBitIndex
to implement
to implement select{0,1}
queries
for succinct dictionaries.
countBits :: Vector Bit -> Int Source #
Return the number of set bits in a vector (population count, popcount).
>>>
countBits (read "[1,1,0,1,0,1]")
4
One can combine countBits
with take
to implement rank{0,1}
queries
for succinct dictionaries.
listBits :: Vector Bit -> [Int] Source #
Return the indices of set bits in a vector.
>>>
listBits (read "[1,1,0,1,0,1]")
[0,1,3,5]
selectBits :: Vector Bit -> Vector Bit -> Vector Bit Source #
For each set bit of the first argument, deposit the corresponding bit of the second argument to the result. Similar to the parallel deposit instruction (PDEP).
>>>
selectBits (read "[0,1,0,1,1]") (read "[1,1,0,0,1]")
[1,0,1]
Here is a reference (but slow) implementation:
import qualified Data.Vector.Unboxed as U selectBits mask ws == U.map snd (U.filter (unBit . fst) (U.zip mask ws))
excludeBits :: Vector Bit -> Vector Bit -> Vector Bit Source #
For each unset bit of the first argument, deposit the corresponding bit of the second argument to the result.
>>>
excludeBits (read "[0,1,0,1,1]") (read "[1,1,0,0,1]")
[1,0]
Here is a reference (but slow) implementation:
import qualified Data.Vector.Unboxed as U excludeBits mask ws == U.map snd (U.filter (not . unBit . fst) (U.zip mask ws))
Mutable conversions
castFromWordsM :: MVector s Word -> MVector s Bit Source #
Cast a vector of words to a vector of bits.
Cf. castFromWords
.
castToWordsM :: MVector s Bit -> Maybe (MVector s Word) Source #
Try to cast a vector of bits to a vector of words.
It succeeds if a vector of bits is aligned.
Use cloneToWordsM
otherwise.
Cf. castToWords
.
cloneToWordsM :: PrimMonad m => MVector (PrimState m) Bit -> m (MVector (PrimState m) Word) Source #
Clone a vector of bits to a new unboxed vector of words.
If the bits don't completely fill the words, the last word will be zero-padded.
Cf. cloneToWords
.
Mutable operations
zipInPlace :: forall m. PrimMonad m => (forall a. Bits a => a -> a -> a) -> Vector Bit -> MVector (PrimState m) Bit -> m () Source #
Zip two vectors with the given function.
rewriting contents of the second argument.
Cf. zipBits
.
>>>
import Data.Bits
>>>
modify (zipInPlace (.&.) (read "[1,1,0]")) (read "[0,1,1]")
[0,1,0]
Warning: if the immutable vector is shorter than the mutable one, it is a caller's responsibility to trim the result:
>>>
import Data.Bits
>>>
modify (zipInPlace (.&.) (read "[1,1,0]")) (read "[0,1,1,1,1,1]")
[0,1,0,1,1,1] -- note trailing garbage
invertInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m () Source #
Invert (flip) all bits in-place.
>>>
Data.Vector.Unboxed.modify invertInPlace (read "[0,1,0,1,0]")
[1,0,1,0,1]
reverseInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m () Source #
Reverse the order of bits in-place.
>>>
Data.Vector.Unboxed.modify reverseInPlace (read "[1,1,0,1,0]")
[0,1,0,1,1]
Consider using vector-rotcev
package
to reverse vectors in O(1) time.
selectBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int Source #
Same as selectBits
, but deposit
selected bits in-place. Returns a number of selected bits.
It is caller's responsibility to trim the result to this number.
excludeBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int Source #
Same as excludeBits
, but deposit
excluded bits in-place. Returns a number of excluded bits.
It is caller's responsibility to trim the result to this number.
Binary polynomials
Binary polynomials of one variable, backed
by an unboxed Vector
Bit
.
Polynomials are stored normalized, without leading zero coefficients.
Ord
instance does not make much sense mathematically,
it is defined only for the sake of Set
, Map
, etc.
>>>
:set -XBinaryLiterals
>>>
-- (1 + x) (1 + x + x^2) = 1 + x^3 (mod 2)
>>>
0b11 * 0b111 :: F2Poly
0b1001
Instances
Enum F2Poly Source # | |
Defined in Data.Bit.F2PolyTS | |
Eq F2Poly Source # | |
Integral F2Poly Source # |
|
Num F2Poly Source # | Addition and multiplication are evaluated modulo 2.
|
Ord F2Poly Source # | |
Real F2Poly Source # | |
Defined in Data.Bit.F2PolyTS toRational :: F2Poly -> Rational # | |
Show F2Poly Source # | |
Generic F2Poly Source # | |
NFData F2Poly Source # | |
Defined in Data.Bit.F2PolyTS | |
type Rep F2Poly Source # | |
Defined in Data.Bit.F2PolyTS |
unF2Poly :: F2Poly -> Vector Bit Source #
Convert F2Poly
to a vector of coefficients
(first element corresponds to a constant term).
toF2Poly :: Vector Bit -> F2Poly Source #
Make F2Poly
from a list of coefficients
(first element corresponds to a constant term).
gcdExt :: F2Poly -> F2Poly -> (F2Poly, F2Poly) Source #
Execute the extended Euclidean algorithm.
For polynomials a
and b
, compute their unique greatest common divisor g
and the unique coefficient polynomial s
satisfying as + bt = g
.
>>>
:set -XBinaryLiterals
>>>
gcdExt 0b101 0b0101
(0b101,0b0)>>>
gcdExt 0b11 0b111
(0b1,0b10)