Safe Haskell | Trustworthy |
---|
- module Data.Bit
- wordSize :: Int
- wordLength :: Vector Bit -> Int
- fromWords :: Int -> Vector Word -> Vector Bit
- toWords :: Vector Bit -> Vector Word
- indexWord :: Vector Bit -> Int -> Word
- pad :: Int -> Vector Bit -> Vector Bit
- padWith :: Bit -> Int -> Vector Bit -> Vector Bit
- zipWords :: (Word -> Word -> Word) -> Vector Bit -> Vector Bit -> Vector Bit
- union :: Vector Bit -> Vector Bit -> Vector Bit
- unions :: Int -> [Vector Bit] -> Vector Bit
- intersection :: Vector Bit -> Vector Bit -> Vector Bit
- intersections :: Int -> [Vector Bit] -> Vector Bit
- difference :: Vector Bit -> Vector Bit -> Vector Bit
- symDiff :: Vector Bit -> Vector Bit -> Vector Bit
- invert :: Vector Bit -> Vector Bit
- select :: (Vector v1 Bit, Vector v2 t) => v1 Bit -> v2 t -> [t]
- selectBits :: Vector Bit -> Vector Bit -> Vector Bit
- exclude :: (Vector v1 Bit, Vector v2 t) => v1 Bit -> v2 t -> [t]
- excludeBits :: Vector Bit -> Vector Bit -> Vector Bit
- countBits :: Vector Bit -> Int
- listBits :: Vector Bit -> [Int]
- and :: Vector Bit -> Bool
- or :: Vector Bit -> Bool
- any :: Num a => (a -> Bool) -> Vector Bit -> Bool
- allBits, anyBits :: Bit -> Vector Bit -> Bool
- all :: Num a => (a -> Bool) -> Vector Bit -> Bool
- reverse :: Vector Bit -> Vector Bit
- first :: Bit -> Vector Bit -> Maybe Int
- findIndex :: Num a => (a -> Bool) -> Vector Bit -> Maybe Int
Documentation
module Data.Bit
wordLength :: Vector Bit -> IntSource
fromWords :: Int -> Vector Word -> Vector BitSource
Given a number of bits and a vector of words, concatenate them to a vector of bits (interpreting the words in little-endian order, as described at indexWord
). If there are not enough words for the number of bits requested, the vector will be zero-padded.
toWords :: Vector Bit -> Vector WordSource
Given a vector of bits, extract an unboxed vector of words. If the bits don't completely fill the words, the last word will be zero-padded.
indexWord :: Vector Bit -> Int -> WordSource
read a word at the given bit offset in little-endian order (i.e., the LSB will correspond to the bit at the given address, the 2's bit will correspond to the address + 1, etc.). If the offset is such that the word extends past the end of the vector, the result is zero-padded.
zipWords :: (Word -> Word -> Word) -> Vector Bit -> Vector Bit -> Vector BitSource
zipWords f xs ys
= fromWords (min (length xs) (length ys)) (zipWith f (toWords xs) (toWords ys))
select :: (Vector v1 Bit, Vector v2 t) => v1 Bit -> v2 t -> [t]Source
Given a vector of bits and a vector of things, extract those things for which the corresponding bit is set.
For example, select (V.map (fromBool . p) x) x == V.filter p x
.
exclude :: (Vector v1 Bit, Vector v2 t) => v1 Bit -> v2 t -> [t]Source
Given a vector of bits and a vector of things, extract those things for which the corresponding bit is unset.
For example, exclude (V.map (fromBool . p) x) x == V.filter (not . p) x
.