bitvec-1.0.0.1: Space-efficient bit vectors

Copyright(c) 2019 Andrew Lelechenko 2012-2016 James Cook
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Bit

Contents

Description

This module exposes an interface with thread-unsafe writes and flips. Consider using Data.Bit.ThreadSafe, which is thread-safe, but slower (up to 20%).

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 10% slower.

Constructors

Bit 

Fields

Instances
Bounded Bit Source # 
Instance details

Defined in Data.Bit.Internal

Methods

minBound :: Bit #

maxBound :: Bit #

Enum Bit Source # 
Instance details

Defined in Data.Bit.Internal

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.Internal

Methods

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

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

Ord Bit Source # 
Instance details

Defined in Data.Bit.Internal

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.Internal

Show Bit Source # 
Instance details

Defined in Data.Bit.Internal

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Bits Bit Source # 
Instance details

Defined in Data.Bit.Internal

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.Internal

Unbox Bit Source # 
Instance details

Defined in Data.Bit.Internal

Vector Vector Bit Source # 
Instance details

Defined in Data.Bit.Internal

MVector MVector Bit Source # 
Instance details

Defined in Data.Bit.Internal

data Vector Bit Source # 
Instance details

Defined in Data.Bit.Internal

data MVector s Bit Source # 
Instance details

Defined in Data.Bit.Internal

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 2x faster.

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 2x faster.

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 a vector of words to a 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 a vector of bits to a 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 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. cloneToWordsM.

>>> cloneToWords (read "[1,1,0,1,1,1,1,0]")
[123]

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 16x faster.

>>> 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]

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

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

Invert (flip) all bits in-place.

Combine with modify or simply resort to map complement to operate on immutable vectors.

>>> Data.Vector.Unboxed.modify invertInPlace (read "[0,1,0,1,0]")
[1,0,1,0,1]

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

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 resposibility 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 resposibility to trim the result to this number.

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

Reverse the order of bits in-place.

Combine with modify or simply resort to reverse to operate on immutable vectors.

>>> Data.Vector.Unboxed.modify reverseInPlace (read "[1,1,0,1,0]")
[0,1,0,1,1]