bitstream-0.2.0.1: Fast, packed, strict and lazy bit streams with stream fusion

Data.Bitstream

Contents

Description

Fast, packed, strict bit streams (i.e. list of Bools) with semi-automatic stream fusion.

This module is intended to be imported qualified, to avoid name clashes with Prelude functions. e.g.

 import qualified Data.BitStream as BS

Strict Bitstreams are made of strict Vector of Packets, and each Packets have at least 1 bit.

Synopsis

Data types

data Bitstream d Source

A space-efficient representation of a Bool vector, supporting many efficient operations. Bitstreams have an idea of directions controlling how octets are interpreted as bits. There are two types of concrete Bitstreams: Bitstream Left and Bitstream Right.

Instances

Bitstream (Bitstream d) => Eq (Bitstream d) 
Bitstream (Bitstream d) => Ord (Bitstream d)

Bitstreams are lexicographically ordered.

 let x = pack [True , False, False]
     y = pack [False, True , False]
     z = pack [False]
 in
   [ compare x y -- GT
   , compare z y -- LT
   ]
Show (Packet d) => Show (Bitstream d) 
Bitstream (Bitstream d) => Monoid (Bitstream d)

Bitstream forms Monoid in the same way as ordinary lists:

 mempty  = empty
 mappend = append
 mconcat = concat
Bitstream (Bitstream Right) 
Bitstream (Bitstream Left) 

data Left Source

Left bitstreams interpret an octet as a vector of bits whose LSB comes first and MSB comes last e.g.

  • 11110000 => [False, False, False, False, True, True , True , True]
  • 10010100 => [False, False, True , False, True, False, False, True]

Bits operations (like toBits) treat a Left bitstream as a little-endian integer.

data Right Source

Right bitstreams interpret an octet as a vector of bits whose MSB comes first and LSB comes last e.g.

  • 11110000 => [True, True , True , True, False, False, False, False]
  • 10010100 => [True, False, False, True, False, True , False, False]

Bits operations (like toBits) treat a Right bitstream as a big-endian integer.

Introducing and eliminating Bitstreams

empty :: Bitstream α => αSource

O(1) The empty Bitstream.

(∅) :: Bitstream α => αSource

(∅) = empty

U+2205, EMPTY SET

singleton :: Bitstream α => Bool -> αSource

O(1) Convert a Bool into a Bitstream.

pack :: Bitstream α => [Bool] -> αSource

O(n) Convert a [Bool] into a Bitstream.

unpack :: Bitstream α => α -> [Bool]Source

O(n) Convert a Bitstream into a [Bool].

fromPackets :: Bitstream (Packet d) => Vector (Packet d) -> Bitstream dSource

O(n) Convert a Vector of Packets into a Bitstream.

unsafeFromPackets :: Bitstream (Packet d) => Int -> Vector (Packet d) -> Bitstream dSource

O(1) Convert a Vector of Packets into a Bitstream, with provided overall bit length. The correctness of the bit length isn't checked, so you MUST be sure your bit length is absolutely correct.

toPackets :: Bitstream d -> Vector (Packet d)Source

O(1) Convert a Bitstream into a Vector of Packets.

Converting from/to strict ByteStrings

fromByteString :: ByteString -> Bitstream dSource

O(n) Convert a strict ByteString into a strict Bitstream.

toByteString :: forall d. (Bitstream (Bitstream d), Bitstream (Packet d)) => Bitstream d -> ByteStringSource

O(n) toByteString bits converts a strict Bitstream bits into a strict ByteString. The resulting octets will be padded with zeroes if the length of bs is not multiple of 8.

Converting from/to Bits'

fromBits :: (Integral β, Bits β, Bitstream α) => β -> αSource

O(n) Convert a Bits into a Bitstream. Note that this function is undefined for instances of Bits which have no fixed bitSize (like Integer).

fromNBits :: (Integral n, Integral β, Bits β, Bitstream α) => n -> β -> αSource

O(n) Convert the lower n bits of the given Bits. In the case that more bits are requested than the Bits provides, this acts as if the Bits has an infinite number of leading 0 bits.

toBits :: (Bitstream α, Bits β) => α -> βSource

O(n) Convert a Bitstream into a Bits.

Converting from/to Streams

stream :: Bitstream α => α -> Stream BoolSource

O(n) Explicitly convert a Bitstream into a Stream of Bool.

Bitstream operations are automatically fused whenever it's possible, safe, and effective to do so, but sometimes you may find the rules are too conservative. These two functions stream and unstream provide a means for coercive stream fusion.

You should be careful when you use stream. Most functions in this package are optimised to minimise frequency of memory allocations and copyings, but getting Bitstreams back from Stream Bool requires the whole Bitstream to be constructed from scratch. Moreover, for lazy Bitstreams this leads to be an incorrect strictness behaviour because lazy Bitstreams are represented as lists of strict Bitstream chunks but stream can't preserve the original chunk structure. Let's say you have a lazy Bitstream with the following chunks:

 bs = [chunk1, chunk2, chunk3, ...]

and you want to drop the first bit of such stream. Our tail is only strict on the chunk1 and will produce the following chunks:

 tail bs = [chunk0, chunk1', chunk2, chunk3, ...]

where chunk0 is a singleton vector of the first packet of chunk1 whose first bit is dropped, and chunk1' is a vector of remaining packets of the chunk1. Neither chunk2 nor chunk3 have to be evaluated here as you might expect.

But think about the following expression:

 import qualified Data.Vector.Fusion.Stream as Stream
 unstream $ Stream.tail $ stream bs

the resulting chunk structure will be:

 [chunk1', chunk2', chunk3', ...]

where each and every chunks are slightly different from the original chunks, and this time chunk1' has the same length as chunk1 but the last bit of chunk1' is from the first bit of chunk2. This means when you next time apply some functions strict on the first chunk, you end up fully evaluating chunk2 as well as chunk1 and this can be a serious misbehaviour for lazy Bitstreams.

The automatic fusion rules are carefully designed to fire only when there aren't any reason to preserve the original packet / chunk structure.

unstream :: Bitstream α => Stream Bool -> αSource

O(n) Convert a Stream of Bool into a Bitstream.

streamPackets :: Bitstream d -> Stream (Packet d)Source

O(1) Convert a Bitstream into a Stream of Packets.

unstreamPackets :: Bitstream (Packet d) => Stream (Packet d) -> Bitstream dSource

O(n) Convert a Stream of Packets into Bitstream.

Changing bit order in octets

directionLToR :: Bitstream Left -> Bitstream RightSource

O(n) Convert a Bitstream Left into a Bitstream Right. Bit directions only affect octet-based operations such as toByteString.

directionRToL :: Bitstream Right -> Bitstream LeftSource

O(n) Convert a Bitstream Right into a Bitstream Left. Bit directions only affect octet-based operations such as toByteString.

Basic interface

cons :: Bitstream α => Bool -> α -> αSource

strict: O(n), lazy: O(1) cons is an analogous to (:) for lists.

snoc :: Bitstream α => α -> Bool -> αSource

O(n) Append a bit to the end of a Bitstream.

append :: Bitstream α => α -> α -> αSource

O(n) Append two Bitstreams.

(⧺) :: Bitstream α => α -> α -> αSource

(⧺) = append

U+29FA, DOUBLE PLUS

head :: Bitstream α => α -> BoolSource

O(1) Extract the first bit of a non-empty Bitstream. An exception will be thrown if empty.

last :: Bitstream α => α -> BoolSource

strict: O(1), lazy: O(n) Extract the last bit of a finite Bitstream. An exception will be thrown if empty.

tail :: Bitstream α => α -> αSource

O(1) Extract the bits after the head of a non-empty Bitstream. An exception will be thrown if empty.

init :: Bitstream α => α -> αSource

O(n) Return all the bits of a Bitstream except the last one. An exception will be thrown if empty.

null :: Bitstream α => α -> BoolSource

O(1) Test whether a Bitstream is empty.

length :: Bitstream α => Num n => α -> nSource

strict: O(1), lazy: O(n) Return the length of a finite Bitstream.

Transforming Bitstreams

map :: Bitstream α => (Bool -> Bool) -> α -> αSource

O(n) Map a function over a Bitstream.

reverse :: Bitstream α => α -> αSource

O(n) Reverse a Bitstream.

Reducing Bitstreams

foldl :: Bitstream α => (β -> Bool -> β) -> β -> α -> βSource

O(n) foldl, applied to a binary operator, a starting value (typically the left-identity of the operator), and a Bitstream, reduces the Bitstream using the binary operator, from left to right:

 foldl f z [x1, x2, ..., xn] == (...((z f x1) f x2) f...) f xn

The Bitstream must be finite.

foldl' :: Bitstream α => (β -> Bool -> β) -> β -> α -> βSource

O(n) foldl' is a variant of foldl that is strict on the accumulator.

foldl1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> BoolSource

O(n) foldl1 is a variant of foldl that has no starting value argument, and thus must be applied to non-empty Bitstreams.

foldl1' :: Bitstream α => (Bool -> Bool -> Bool) -> α -> BoolSource

O(n) A strict version of foldl1.

foldr :: Bitstream α => (Bool -> β -> β) -> β -> α -> βSource

O(n) foldr, applied to a binary operator, a starting value (typically the right-identity of the operator), and a Bitstream, reduces the Bitstream using the binary operator, from right to left:

 foldr f z [x1, x2, ..., xn] == x1 f (x2 f ... (xn f z)...)

foldr1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> BoolSource

O(n) foldr1 is a variant of foldr that has no starting value argument, and thus must be applied to non-empty Bitstreams.

Special folds

concat :: Bitstream α => [α] -> αSource

O(n) Concatenate all Bitstreams in the list.

concatMap :: Bitstream α => (Bool -> α) -> α -> αSource

Map a function over a Bitstream and concatenate the results.

and :: Bitstream α => α -> BoolSource

O(n) and returns the conjunction of a Bool list. For the result to be True, the Bitstream must be finite; False, however, results from a False value at a finite index of a finite or infinite Bitstream. Note that strict Bitstreams are always finite.

or :: Bitstream α => α -> BoolSource

O(n) or returns the disjunction of a Bool list. For the result to be False, the Bitstream must be finite; True, however, results from a True value at a finite index of a finite or infinite Bitstream. Note that strict Bitstreams are always finite.

any :: Bitstream α => (Bool -> Bool) -> α -> BoolSource

O(n) Applied to a predicate and a Bitstream, any determines if any bit of the Bitstream satisfies the predicate. For the result to be False, the Bitstream must be finite; True, however, results from a True value for the predicate applied to a bit at a finite index of a finite or infinite Bitstream.

all :: Bitstream α => (Bool -> Bool) -> α -> BoolSource

O(n) Applied to a predicate and a Bitstream, all determines if all bits of the Bitstream satisfy the predicate. For the result to be True, the Bitstream must be finite; False, however, results from a False value for the predicate applied to a bit at a finite index of a finite or infinite Bitstream.

Building Bitstreams

Scans

scanl :: Bitstream α => (Bool -> Bool -> Bool) -> Bool -> α -> αSource

O(n) scanl is similar to foldl, but returns a Bitstream of successive reduced bits from the left:

 scanl f z [x1, x2, ...] == [z, z f x1, (z f x1) f x2, ...]

Note that

 last (scanl f z xs) == foldl f z xs

scanl1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> αSource

O(n) scanl1 is a variant of scanl that has no starting value argument:

 scanl1 f [x1, x2, ...] == [x1, x1 f x2, ...]

scanr :: Bitstream α => (Bool -> Bool -> Bool) -> Bool -> α -> αSource

O(n) scanr is the right-to-left dual of scanl. Note that

 head (scanr f z xs) == foldr f z xs

scanr1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> αSource

O(n) scanr1 is a variant of scanr that has no starting value argument.

Replication

replicate :: (Integral n, Bitstream α) => n -> Bool -> αSource

O(n) replicate n x is a Bitstream of length n with x the value of every bit.

Unfolding

unfoldr :: Bitstream α => (β -> Maybe (Bool, β)) -> β -> αSource

O(n) The unfoldr function is a `dual' to foldr: while foldr reduces a Bitstream to a summary value, unfoldr builds a Bitstream from a seed value. The function takes the element and returns Nothing if it is done producing the Bitstream or returns Just (a, b), in which case, a is a prepended to the Bitstream and b is used as the next element in a recursive call.

unfoldrN :: (Integral n, Bitstream α) => n -> (β -> Maybe (Bool, β)) -> β -> αSource

O(n) unfoldrN is a variant of unfoldr but constructs a Bitstream with at most n bits.

Substreams

take :: (Integral n, Bitstream α) => n -> α -> αSource

O(n) take n, applied to a Bitstream xs, returns the prefix of xs of length n, or xs itself if n > length xs.

drop :: (Integral n, Bitstream α) => n -> α -> αSource

O(n) drop n xs returns the suffix of xs after the first n bits, or empty if n > length xs.

takeWhile :: Bitstream α => (Bool -> Bool) -> α -> αSource

O(n) takeWhile, applied to a predicate p and a Bitstream xs, returns the longest prefix (possibly empty) of xs of bits that satisfy p.

dropWhile :: Bitstream α => (Bool -> Bool) -> α -> αSource

O(n) dropWhile p xs returns the suffix remaining after takeWhile p xs.

span :: Bitstream α => (Bool -> Bool) -> α -> (α, α)Source

O(n) span, applied to a predicate p and a Bitstream xs, returns a tuple where first element is longest prefix (possibly empty) of xs of bits that satisfy p and second element is the remainder of the Bitstream.

span p xs is equivalent to (takeWhile p xs, dropWhile p xs)

break :: Bitstream α => (Bool -> Bool) -> α -> (α, α)Source

O(n) break, applied to a predicate p and a Bitstream xs, returns a tuple where first element is longest prefix (possibly empty) of xs of bits that do not satisfy p and second element is the remainder of the Bitstream.

break p is equivalent to span (not . p).

Searching streams

Searching by equality

elem :: Bitstream α => Bool -> α -> BoolSource

O(n) elem is the Bitstream membership predicate, usually written in infix form, e.g., x `elem` xs. For the result to be False, the Bitstream must be finite; True, however, results from an bit equal to x found at a finite index of a finite or infinite Bitstream.

(∈) :: Bitstream α => Bool -> α -> BoolSource

(∈) = elem

U+2208, ELEMENT OF

(∋) :: Bitstream α => α -> Bool -> BoolSource

(∋) = flip (∈)

U+220B, CONTAINS AS MEMBER

notElem :: Bitstream α => Bool -> α -> BoolSource

O(n) notElem is the negation of elem.

(∉) :: Bitstream α => Bool -> α -> BoolSource

(∉) = notElem

U+2209, NOT AN ELEMENT OF

(∌) :: Bitstream α => α -> Bool -> BoolSource

(∌) = flip (∉)

U+220C, DOES NOT CONTAIN AS MEMBER

Searching with a predicate

find :: Bitstream α => (Bool -> Bool) -> α -> Maybe BoolSource

O(n) The find function takes a predicate and a Bitstream and returns the bit in the Bitstream matching the predicate, or Nothing if there is no such bit.

filter :: Bitstream α => (Bool -> Bool) -> α -> αSource

O(n) filter, applied to a predicate and a Bitstream, returns the Bitstream of those bits that satisfy the predicate.

partition :: Bitstream α => (Bool -> Bool) -> α -> (α, α)Source

O(n) The partition function takes a predicate and a Bitstream and returns the pair of Bitstreams of bits which do and do not satisfy the predicate, respectively.

Indexing streams

(!!) :: (Bitstream α, Integral n) => α -> n -> BoolSource

O(n) Bitstream index (subscript) operator, starting from 0.

elemIndex :: (Bitstream α, Integral n) => Bool -> α -> Maybe nSource

O(n) The elemIndex function returns the index of the first bit in the given Bitstream which is equal to the query bit, or Nothing if there is no such bit.

elemIndices :: (Bitstream α, Integral n) => Bool -> α -> [n]Source

O(n) The elemIndices function extends elemIndex, by returning the indices of all bits equal to the query bit, in ascending order.

findIndex :: (Bitstream α, Integral n) => (Bool -> Bool) -> α -> Maybe nSource

O(n) The findIndex function takes a predicate and a Bitstream and returns the index of the first bit in the Bitstream satisfying the predicate, or Nothing if there is no such bit.

findIndices :: (Bitstream α, Integral n) => (Bool -> Bool) -> α -> [n]Source

O(n) The findIndices function extends findIndex, by returning the indices of all bits satisfying the predicate, in ascending order.

Zipping and unzipping streams

zip :: Bitstream α => α -> α -> [(Bool, Bool)]Source

O(min(m, n)) zip takes two Bitstreams and returns a list of corresponding bit pairs. If one input Bitstream is short, excess bits of the longer Bitstream are discarded.

zip3 :: Bitstream α => α -> α -> α -> [(Bool, Bool, Bool)]Source

The zip3 function takes three Bitstreams and returns a list of triples, analogous to zip.

zip4 :: Bitstream α => α -> α -> α -> α -> [(Bool, Bool, Bool, Bool)]Source

The zip4 function takes four lists and returns a list of quadruples, analogous to zip.

zip5 :: Bitstream α => α -> α -> α -> α -> α -> [(Bool, Bool, Bool, Bool, Bool)]Source

The zip5 function takes five Bitstreams and returns a list of five-tuples, analogous to zip.

zip6 :: Bitstream α => α -> α -> α -> α -> α -> α -> [(Bool, Bool, Bool, Bool, Bool, Bool)]Source

The zip6 function takes six Bitstreams and returns a list of six-tuples, analogous to zip.

zipWith :: Bitstream α => (Bool -> Bool -> β) -> α -> α -> [β]Source

O(min(m, n)) zipWith generalises zip by zipping with the function given as the first argument, instead of a tupling function.

zipWith3 :: Bitstream α => (Bool -> Bool -> Bool -> β) -> α -> α -> α -> [β]Source

The zipWith3 function takes a function which combines three bits, as well as three Bitstreams and returns a list of their point-wise combination, analogous to zipWith.

zipWith4 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> [β]Source

The zipWith4 function takes a function which combines four bits, as well as four Bitstreams and returns a list of their point-wise combination, analogous to zipWith.

zipWith5 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> [β]Source

The zipWith5 function takes a function which combines five bits, as well as five Bitstreams and returns a list of their point-wise combination, analogous to zipWith.

zipWith6 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> α -> [β]Source

The zipWith6 function takes a function which combines six bits, as well as six Bitstreams and returns a list of their point-wise combination, analogous to zipWith.

unzip :: Bitstream α => [(Bool, Bool)] -> (α, α)Source

O(min(m, n)) unzip transforms a list of bit pairs into a Bitstream of first components and a Bitstream of second components.

unzip3 :: Bitstream α => [(Bool, Bool, Bool)] -> (α, α, α)Source

The unzip3 function takes a list of triples and returns three Bitstreams, analogous to unzip.

unzip4 :: Bitstream α => [(Bool, Bool, Bool, Bool)] -> (α, α, α, α)Source

The unzip4 function takes a list of quadruples and returns four Bitstreams, analogous to unzip.

unzip5 :: Bitstream α => [(Bool, Bool, Bool, Bool, Bool)] -> (α, α, α, α, α)Source

The unzip5 function takes a list of five-tuples and returns five Bitstreams, analogous to unzip.

unzip6 :: Bitstream α => [(Bool, Bool, Bool, Bool, Bool, Bool)] -> (α, α, α, α, α, α)Source

The unzip6 function takes a list of six-tuples and returns six Bitstreams, analogous to unzip.

I/O with Bitstreams

Standard input and output

getContents :: Bitstream (Packet d) => IO (Bitstream d)Source

O(n) Read a Bitstream from the stdin strictly, equivalent to hGetContents stdin. The Handle is closed after the contents have been read.

putBits :: (Bitstream (Bitstream d), Bitstream (Packet d)) => Bitstream d -> IO ()Source

O(n) Write a Bitstream to the stdout, equivalent to hPut stdout.

interact :: (Bitstream (Bitstream d), Bitstream (Packet d)) => (Bitstream d -> Bitstream d) -> IO ()Source

The interact function takes a function of type Bitstream d -> Bitstream d as its argument. The entire input from the stdin is passed to this function as its argument, and the resulting Bitstream is output on the stdout.

Files

readFile :: Bitstream (Packet d) => FilePath -> IO (Bitstream d)Source

O(n) Read an entire file strictly into a Bitstream.

writeFile :: (Bitstream (Bitstream d), Bitstream (Packet d)) => FilePath -> Bitstream d -> IO ()Source

O(n) Write a Bitstream to a file.

appendFile :: (Bitstream (Bitstream d), Bitstream (Packet d)) => FilePath -> Bitstream d -> IO ()Source

O(n) Append a Bitstream to a file.

I/O with Handles

hGetContents :: Bitstream (Packet d) => Handle -> IO (Bitstream d)Source

O(n) Read entire handle contents strictly into a Bitstream.

This function reads chunks at a time, doubling the chunksize on each read. The final buffer is then realloced to the appropriate size. For files > half of available memory, this may lead to memory exhaustion. Consider using readFile in this case.

The Handle is closed once the contents have been read, or if an exception is thrown.

hGet :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)Source

O(n) hGet h n reads a Bitstream directly from the specified Handle h. First argument h is the Handle to read from, and the second n is the number of octets to read, not bits. It returns the octets read, up to n, or null if EOF has been reached.

If the handle is a pipe or socket, and the writing end is closed, hGet will behave as if EOF was reached.

hGetSome :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)Source

O(n) Like hGet, except that a shorter Bitstream may be returned if there are not enough octets immediately available to satisfy the whole request. hGetSome only blocks if there is no data available, and EOF has not yet been reached.

hGetNonBlocking :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)Source

O(n) hGetNonBlocking is similar to hGet, except that it will never block waiting for data to become available. If there is no data available to be read, hGetNonBlocking returns empty.

hPut :: (Bitstream (Bitstream d), Bitstream (Packet d)) => Handle -> Bitstream d -> IO ()Source

O(n) Write a Bitstream to the given Handle.