bitvec-1.1.1.0: Space-efficient bit vectors
Copyright(c) 2019-2020 Andrew Lelechenko 2012-2016 James Cook
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Bit.ThreadSafe

Description

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

Documentation

newtype Bit Source #

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.

Constructors

Bit 

Fields

Instances

Instances details
Bounded Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

minBound :: Bit #

maxBound :: Bit #

Enum Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

succ :: Bit -> Bit #

pred :: Bit -> Bit #

toEnum :: Int -> Bit #

fromEnum :: Bit -> Int #

enumFrom :: Bit -> [Bit] #

enumFromThen :: Bit -> Bit -> [Bit] #

enumFromTo :: Bit -> Bit -> [Bit] #

enumFromThenTo :: Bit -> Bit -> Bit -> [Bit] #

Eq Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

(==) :: Bit -> Bit -> Bool #

(/=) :: Bit -> Bit -> Bool #

Fractional Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

(/) :: Bit -> Bit -> Bit #

recip :: Bit -> Bit #

fromRational :: Rational -> Bit #

Integral Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

quot :: Bit -> Bit -> Bit #

rem :: Bit -> Bit -> Bit #

div :: Bit -> Bit -> Bit #

mod :: Bit -> Bit -> Bit #

quotRem :: Bit -> Bit -> (Bit, Bit) #

divMod :: Bit -> Bit -> (Bit, Bit) #

toInteger :: Bit -> Integer #

Num Bit Source #

There is only one lawful Num instance possible with + = xor and fromInteger = Bit . odd.

Instance details

Defined in Data.Bit.InternalTS

Methods

(+) :: Bit -> Bit -> Bit #

(-) :: Bit -> Bit -> Bit #

(*) :: Bit -> Bit -> Bit #

negate :: Bit -> Bit #

abs :: Bit -> Bit #

signum :: Bit -> Bit #

fromInteger :: Integer -> Bit #

Ord Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

compare :: Bit -> Bit -> Ordering #

(<) :: Bit -> Bit -> Bool #

(<=) :: Bit -> Bit -> Bool #

(>) :: Bit -> Bit -> Bool #

(>=) :: Bit -> Bit -> Bool #

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Read Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Real Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

toRational :: Bit -> Rational #

Show Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Generic Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Associated Types

type Rep Bit :: Type -> Type #

Methods

from :: Bit -> Rep Bit x #

to :: Rep Bit x -> Bit #

Bits Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

(.&.) :: Bit -> Bit -> Bit #

(.|.) :: Bit -> Bit -> Bit #

xor :: Bit -> Bit -> Bit #

complement :: Bit -> Bit #

shift :: Bit -> Int -> Bit #

rotate :: Bit -> Int -> Bit #

zeroBits :: Bit #

bit :: Int -> Bit #

setBit :: Bit -> Int -> Bit #

clearBit :: Bit -> Int -> Bit #

complementBit :: Bit -> Int -> Bit #

testBit :: Bit -> Int -> Bool #

bitSizeMaybe :: Bit -> Maybe Int #

bitSize :: Bit -> Int #

isSigned :: Bit -> Bool #

shiftL :: Bit -> Int -> Bit #

unsafeShiftL :: Bit -> Int -> Bit #

shiftR :: Bit -> Int -> Bit #

unsafeShiftR :: Bit -> Int -> Bit #

rotateL :: Bit -> Int -> Bit #

rotateR :: Bit -> Int -> Bit #

popCount :: Bit -> Int #

FiniteBits Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

NFData Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Methods

rnf :: Bit -> () #

Unbox Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Vector Vector Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

MVector MVector Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

Bits (Vector Bit) Source # 
Instance details

Defined in Data.Bit.ImmutableTS

type Rep Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

type Rep Bit = D1 ('MetaData "Bit" "Data.Bit.InternalTS" "bitvec-1.1.1.0-AhfNuieIoBoKwVuNuMi18y" 'True) (C1 ('MetaCons "Bit" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
data Vector Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

data MVector s Bit Source # 
Instance details

Defined in Data.Bit.InternalTS

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.

>>> :set -XOverloadedLists
>>> castFromWords [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.

>>> :set -XOverloadedLists
>>> cloneToWords [1,1,0,1,1,1,1]
[123]

castFromWords8 :: Vector Word8 -> Vector Bit Source #

Cast a unboxed vector of Word8 to an unboxed vector of bits.

>>> :set -XOverloadedLists
>>> castFromWords8 [123]
[1,1,0,1,1,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 bytes, the last Word8 will be zero-padded.

>>> :set -XOverloadedLists
>>> cloneToWords8 [1,1,0,1,1,1,1]
[123]

cloneFromByteString :: ByteString -> Vector Bit Source #

Clone a ByteString to a new unboxed vector of bits.

>>> :set -XOverloadedStrings
>>> cloneFromByteString "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]

cloneToByteString :: Vector Bit -> ByteString Source #

Clone an unboxed vector of bits to a new ByteString. If the bits don't completely fill the bytes, the last character will be zero-padded.

>>> :set -XOverloadedLists
>>> cloneToByteString [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.

Users are strongly encouraged to enable flag libgmp for the ultimate performance of zipBits.

>>> :set -XOverloadedLists
>>> import Data.Bits
>>> zipBits (.&.) [1,1,0] [0,1,1] -- intersection
[0,1,0]
>>> zipBits (.|.) [1,1,0] [0,1,1] -- union
[1,1,1]
>>> zipBits (\x y -> x .&. complement y) [1,1,0] [0,1,1] -- difference
[1,0,0]
>>> zipBits xor [1,1,0] [0,1,1] -- symmetric difference
[1,0,1]

mapBits :: (forall a. Bits a => a -> a) -> Vector Bit -> Vector Bit Source #

Map a vectors with the given function. Similar to map, but faster.

>>> :set -XOverloadedLists
>>> import Data.Bits
>>> mapBits complement [0,1,1]
[1,0,0]

invertBits :: Vector Bit -> Vector Bit Source #

Invert (flip) all bits.

Users are strongly encouraged to enable flag libgmp for the ultimate performance of invertBits.

>>> :set -XOverloadedLists
>>> invertBits [0,1,0,1,0]
[1,0,1,0,1]

reverseBits :: Vector Bit -> Vector Bit Source #

Reverse the order of bits.

>>> :set -XOverloadedLists
>>> reverseBits [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.

>>> :set -XOverloadedLists
>>> bitIndex 1 [0,0,1,0,1]
Just 2
>>> bitIndex 1 [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 1
areAllBitsSet = isNothing . bitIndex 0

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.

>>> :set -XOverloadedLists
>>> nthBitIndex 1 2 [0,1,0,1,1,1,0] -- 2nd occurence of 1
Just 3
>>> nthBitIndex 1 5 [0,1,0,1,1,1,0] -- 5th occurence of 1
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).

Users are strongly encouraged to enable flag libgmp for the ultimate performance of countBits.

>>> :set -XOverloadedLists
>>> countBits [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 0-based indices of set bits in a vector.

>>> :set -XOverloadedLists
>>> listBits [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).

>>> :set -XOverloadedLists
>>> selectBits [0,1,0,1,1] [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.

>>> :set -XOverloadedLists
>>> excludeBits [0,1,0,1,1] [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.

>>> :set -XOverloadedLists
>>> import Data.Bits
>>> Data.Vector.Unboxed.modify (zipInPlace (.&.) [1,1,0]) [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:

>>> :set -XOverloadedLists
>>> import Data.Bits
>>> Data.Vector.Unboxed.modify (zipInPlace (.&.) [1,1,0]) [0,1,1,1,1,1]
[0,1,0,1,1,1] -- note trailing garbage

mapInPlace :: PrimMonad m => (forall a. Bits a => a -> a) -> MVector (PrimState m) Bit -> m () Source #

Apply a function to a mutable vector bitwise, rewriting its contents. Cf. mapBits.

>>> :set -XOverloadedLists
>>> import Data.Bits
>>> Data.Vector.Unboxed.modify (mapInPlace complement) [0,1,1]
[1,0,0]

invertInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m () Source #

Invert (flip) all bits in-place.

>>> :set -XOverloadedLists
>>> Data.Vector.Unboxed.modify invertInPlace [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.

>>> :set -XOverloadedLists
>>> Data.Vector.Unboxed.modify reverseInPlace [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.

>>> :set -XOverloadedLists
>>> import Control.Monad.ST (runST)
>>> import qualified Data.Vector.Unboxed as U
>>> runST $ do { vec <- U.unsafeThaw [1,1,0,0,1]; n <- selectBitsInPlace [0,1,0,1,1] vec; U.take n <$> U.unsafeFreeze vec }
[1,0,1]

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.

>>> :set -XOverloadedLists
>>> import Control.Monad.ST (runST)
>>> import qualified Data.Vector.Unboxed as U
>>> runST $ do { vec <- U.unsafeThaw [1,1,0,0,1]; n <- excludeBitsInPlace [0,1,0,1,1] vec; U.take n <$> U.unsafeFreeze vec }
[1,0]

Binary polynomials

data F2Poly Source #

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

Instances details
Enum F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Eq F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Methods

(==) :: F2Poly -> F2Poly -> Bool #

(/=) :: F2Poly -> F2Poly -> Bool #

Integral F2Poly Source #

toInteger converts a binary polynomial, encoded as F2Poly, to Integer encoding.

Instance details

Defined in Data.Bit.F2PolyTS

Num F2Poly Source #

Addition and multiplication are evaluated modulo 2.

abs = id and signum = const 1.

fromInteger converts a binary polynomial, encoded as Integer, to F2Poly encoding.

Instance details

Defined in Data.Bit.F2PolyTS

Ord F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Real F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Show F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Generic F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Associated Types

type Rep F2Poly :: Type -> Type #

Methods

from :: F2Poly -> Rep F2Poly x #

to :: Rep F2Poly x -> F2Poly #

NFData F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

Methods

rnf :: F2Poly -> () #

type Rep F2Poly Source # 
Instance details

Defined in Data.Bit.F2PolyTS

type Rep F2Poly = D1 ('MetaData "F2Poly" "Data.Bit.F2PolyTS" "bitvec-1.1.1.0-AhfNuieIoBoKwVuNuMi18y" 'True) (C1 ('MetaCons "F2Poly" 'PrefixI 'True) (S1 ('MetaSel ('Just "unF2Poly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Bit))))

unF2Poly :: F2Poly -> Vector Bit Source #

Convert F2Poly to a vector of coefficients (first element corresponds to a constant term).

>>> :set -XBinaryLiterals
>>> unF2Poly 0b1101
[1,0,1,1]

toF2Poly :: Vector Bit -> F2Poly Source #

Make F2Poly from a list of coefficients (first element corresponds to a constant term).

>>> :set -XOverloadedLists
>>> toF2Poly [1,0,1,1,0,0]
0b1101

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)