bv-little-1.1.0: Efficient little-endian bit vector library

Copyright(c) Alex Washburn 2018
LicenseBSD-style
Maintainergithub@recursion.ninja
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.BitVector.LittleEndian

Contents

Description

A bit vector similar to Data.BitVector from the bv, however the endianness is reversed. This module defines little-endian pseudo–size-polymorphic bit vectors.

Little-endian bit vectors are isomorphic to a [Bool] with the least significant bit at the head of the list and the most significant bit at the end of the list. Consequently, the endianness of a bit vector affects the semantics of the following typeclasses:

For an implementation of bit vectors which are isomorphic to a [Bool] with the most significant bit at the head of the list and the least significant bit at the end of the list, use the bv package.

This module does not define numeric instances for BitVector. This is intentional! To interact with a bit vector as an Integral value, convert the BitVector using either toSignedNumber or toUnsignedNumber.

This module defines rank and select operations for BitVector as a succinct data structure. These operations are not o(1) so BitVector is not a true succinct data structure. However, it could potentially be extend to support this in the future.

Synopsis

Documentation

data BitVector Source #

A little-endian bit vector of non-negative dimension.

Instances
Eq BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Data BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitVector -> c BitVector #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitVector #

toConstr :: BitVector -> Constr #

dataTypeOf :: BitVector -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BitVector) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitVector) #

gmapT :: (forall b. Data b => b -> b) -> BitVector -> BitVector #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitVector -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitVector -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitVector -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitVector -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitVector -> m BitVector #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitVector -> m BitVector #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitVector -> m BitVector #

Ord BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Show BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Generic BitVector Source # 
Instance details

Defined in Data.BitVector.LittleEndian

Associated Types

type Rep BitVector :: Type -> Type #

Semigroup BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Monoid BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Arbitrary BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

CoArbitrary BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Methods

coarbitrary :: BitVector -> Gen b -> Gen b #

Bits BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

FiniteBits BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

NFData BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Methods

rnf :: BitVector -> () #

Hashable BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoFunctor BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoFoldable BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

Methods

ofoldMap :: Monoid m => (Element BitVector -> m) -> BitVector -> m #

ofoldr :: (Element BitVector -> b -> b) -> b -> BitVector -> b #

ofoldl' :: (a -> Element BitVector -> a) -> a -> BitVector -> a #

otoList :: BitVector -> [Element BitVector] #

oall :: (Element BitVector -> Bool) -> BitVector -> Bool #

oany :: (Element BitVector -> Bool) -> BitVector -> Bool #

onull :: BitVector -> Bool #

olength :: BitVector -> Int #

olength64 :: BitVector -> Int64 #

ocompareLength :: Integral i => BitVector -> i -> Ordering #

otraverse_ :: Applicative f => (Element BitVector -> f b) -> BitVector -> f () #

ofor_ :: Applicative f => BitVector -> (Element BitVector -> f b) -> f () #

omapM_ :: Applicative m => (Element BitVector -> m ()) -> BitVector -> m () #

oforM_ :: Applicative m => BitVector -> (Element BitVector -> m ()) -> m () #

ofoldlM :: Monad m => (a -> Element BitVector -> m a) -> a -> BitVector -> m a #

ofoldMap1Ex :: Semigroup m => (Element BitVector -> m) -> BitVector -> m #

ofoldr1Ex :: (Element BitVector -> Element BitVector -> Element BitVector) -> BitVector -> Element BitVector #

ofoldl1Ex' :: (Element BitVector -> Element BitVector -> Element BitVector) -> BitVector -> Element BitVector #

headEx :: BitVector -> Element BitVector #

lastEx :: BitVector -> Element BitVector #

unsafeHead :: BitVector -> Element BitVector #

unsafeLast :: BitVector -> Element BitVector #

maximumByEx :: (Element BitVector -> Element BitVector -> Ordering) -> BitVector -> Element BitVector #

minimumByEx :: (Element BitVector -> Element BitVector -> Ordering) -> BitVector -> Element BitVector #

oelem :: Element BitVector -> BitVector -> Bool #

onotElem :: Element BitVector -> BitVector -> Bool #

MonoTraversable BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoKeyed BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoFoldableWithKey BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoTraversableWithKey BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoLookup BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoIndexable BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoAdjustable BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoZip BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

MonoZipWithKey BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

TextShow BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

type Rep BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

type Rep BitVector = D1 (MetaData "BitVector" "Data.BitVector.LittleEndian" "bv-little-1.1.0-inplace" False) (C1 (MetaCons "BV" PrefixI True) (S1 (MetaSel (Just "dim") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word) :*: S1 (MetaSel (Just "nat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural)))
type Element BitVector Source #

Since: 0.1.0

Instance details

Defined in Data.BitVector.LittleEndian

type MonoKey BitVector Source #

Since: 1.0.0

Instance details

Defined in Data.BitVector.LittleEndian

Bit-stream conversion

fromBits :: Foldable f => f Bool -> BitVector Source #

Create a bit vector from a little-endian list of bits.

The following will hold:

length . takeWhile not === countLeadingZeros . fromBits
length . takeWhile not . reverse === countTrailingZeros . fromBits

Time: \(\, \mathcal{O} \left( n \right) \)

Since: 0.1.0

Examples

Expand
>>> fromBits [True, False, False]
[3]1

toBits :: BitVector -> [Bool] Source #

Create a little-endian list of bits from a bit vector.

The following will hold:

length . takeWhile not . toBits === countLeadingZeros
length . takeWhile not . reverse . toBits === countTrailingZeros

Time: \(\, \mathcal{O} \left( n \right) \)

Since: 0.1.0

Examples

Expand
>>> toBits [4]11
[True, True, False, True]

Numeric conversion

fromNumber Source #

Arguments

:: Integral v 
=> Word

dimension of bit vector

-> v

signed, little-endian integral value

-> BitVector 

Create a bit vector of non-negative dimension from an integral value.

The integral value will be treated as an signed number and the resulting bit vector will contain the two's complement bit representation of the number.

The integral value will be interpreted as little-endian so that the least significant bit of the integral value will be the value of the 0th index of the resulting bit vector and the most significant bit of the integral value will be at index dimension − 1.

Note that if the bit representation of the integral value exceeds the supplied dimension, then the most significant bits will be truncated in the resulting bit vector.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> fromNumber 8 96
[8]96
>>> fromNumber 8 -96
[8]160
>>> fromNumber 6 96
[6]32

toSignedNumber :: Num a => BitVector -> a Source #

Two's complement value of a bit vector.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> toSignedNumber [4]0
0
>>> toSignedNumber [4]3
3
>>> toSignedNumber [4]7
7
>>> toSignedNumber [4]8
-8
>>> toSignedNumber [4]12
-4
>>> toSignedNumber [4]15
-1

toUnsignedNumber :: Num a => BitVector -> a Source #

Unsigned value of a bit vector.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> toSignedNumber [4]0
0
>>> toSignedNumber [4]3
3
>>> toSignedNumber [4]7
7
>>> toSignedNumber [4]8
8
>>> toSignedNumber [4]12
12
>>> toSignedNumber [4]15
15

Queries

dimension :: BitVector -> Word Source #

Get the dimension of a BitVector. Preferable to finiteBitSize as it returns a type which cannot represent a non-negative value and a BitVector must have a non-negative dimension.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> dimension [2]3
2
>>> dimension [4]12
4

isZeroVector :: BitVector -> Bool Source #

Determine if any bits are set in the BitVector. Faster than (0 ==) . popCount.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> isZeroVector [2]3
False
>>> isZeroVector [4]0
True

subRange :: (Word, Word) -> BitVector -> BitVector Source #

Get the inclusive range of bits in BitVector as a new BitVector.

If either of the bounds of the subrange exceed the bit vector's dimension, the resulting subrange will append an infinite number of zeroes to the end of the bit vector in order to satisfy the subrange request.

Time: \(\, \mathcal{O} \left( 1 \right) \)

Since: 0.1.0

Examples

Expand
>>> subRange (0,2) [4]7
[3]7
>>> subRange (1, 3) [4]7
[3]3
>>> subRange (2, 4) [4]7
[3]1
>>> subRange (3, 5) [4]7
[3]0
>>> subRange (10, 20) [4]7
[10]0

Rank / Select

rank Source #

Arguments

:: BitVector 
-> Word

\(k\), the rank index

-> Word

Set bits within the rank index

Determine the number of set bits in the BitVector up to, but not including, index k.

To determine the number of unset bits in the BitVector, use k - rank bv k.

Uses "broadword programming." Efficient on small BitVectors (10^3).

Time: \(\, \mathcal{O} \left( \frac{n}{w} \right) \), where \(w\) is the number of bits in a Word.

Since: 1.1.0

Examples

Expand
>>> let bv = fromNumber 128 0 `setBit` 0 `setBit` 65
>>> rank bv   0  -- Count how many ones in the first 0 bits (always returns 0)
0
>>> rank bv   1  -- Count how many ones in the first 1 bits
1
>>> rank bv   2  -- Count how many ones in the first 2 bits
1
>>> rank bv  65  -- Count how many ones in the first 65 bits
1
>>> rank bv  66  -- Count how many ones in the first 66 bits
1
>>> rank bv 128  -- Count how many ones in all 128 bits
2
>>> rank bv 129  -- Out-of-bounds, fails gracefully
2

select Source #

Arguments

:: BitVector 
-> Word

\(k\), the select index

-> Maybe Word

index of the k-th set bit

Find the index of the k-th set bit in the BitVector.

To find the index of the k-th unset bit in the BitVector, use select (complement bv) k.

Uses "broadword programming." Efficient on small BitVectors (10^3).

Time: \(\, \mathcal{O} \left( \frac{n}{w} \right) \), where \(w\) is the number of bits in a Word.

Since: 1.1.0

Examples

Expand
>>> let bv = fromNumber 128 0 `setBit` 0 `setBit` 65
>>> select bv 0  -- Find the 0-indexed position of the first one bit
Just 0
>>> select bv 1  -- Find the 0-indexed position of the second one bit
Just 65
>>> select bv 2  -- There is no 3rd set bit, `select` fails
Nothing