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.
- data Bitstream d
- data Left
- data Right
- empty :: Bitstream α => α
- (∅) :: Bitstream α => α
- singleton :: Bitstream α => Bool -> α
- pack :: Bitstream α => [Bool] -> α
- unpack :: Bitstream α => α -> [Bool]
- fromPackets :: Vector (Packet d) -> Bitstream d
- toPackets :: Bitstream d -> Vector (Packet d)
- fromByteString :: ByteString -> Bitstream d
- toByteString :: forall d. Bitstream (Packet d) => Bitstream d -> ByteString
- stream :: Bitstream α => α -> Stream Bool
- unstream :: Bitstream α => Stream Bool -> α
- directionLToR :: Bitstream Left -> Bitstream Right
- directionRToL :: Bitstream Right -> Bitstream Left
- cons :: Bitstream α => Bool -> α -> α
- snoc :: Bitstream α => α -> Bool -> α
- append :: Bitstream α => α -> α -> α
- (⧺) :: Bitstream α => α -> α -> α
- head :: Bitstream α => α -> Bool
- last :: Bitstream α => α -> Bool
- tail :: Bitstream α => α -> α
- init :: Bitstream α => α -> α
- null :: Bitstream α => α -> Bool
- length :: Bitstream α => Num n => α -> n
- map :: Bitstream α => (Bool -> Bool) -> α -> α
- reverse :: Bitstream α => α -> α
- foldl :: Bitstream α => (β -> Bool -> β) -> β -> α -> β
- foldl' :: Bitstream α => (β -> Bool -> β) -> β -> α -> β
- foldl1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> Bool
- foldl1' :: Bitstream α => (Bool -> Bool -> Bool) -> α -> Bool
- foldr :: Bitstream α => (Bool -> β -> β) -> β -> α -> β
- foldr1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> Bool
- concat :: Bitstream α => [α] -> α
- concatMap :: Bitstream α => (Bool -> α) -> α -> α
- and :: Bitstream α => α -> Bool
- or :: Bitstream α => α -> Bool
- any :: Bitstream α => (Bool -> Bool) -> α -> Bool
- all :: Bitstream α => (Bool -> Bool) -> α -> Bool
- scanl :: Bitstream α => (Bool -> Bool -> Bool) -> Bool -> α -> α
- scanl1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> α
- scanr :: Bitstream α => (Bool -> Bool -> Bool) -> Bool -> α -> α
- scanr1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> α
- replicate :: (Bitstream α, Integral n) => n -> Bool -> α
- unfoldr :: Bitstream α => (β -> Maybe (Bool, β)) -> β -> α
- unfoldrN :: (Bitstream α, Integral n) => n -> (β -> Maybe (Bool, β)) -> β -> α
- take :: (Bitstream α, Integral n) => n -> α -> α
- drop :: (Bitstream α, Integral n) => n -> α -> α
- takeWhile :: Bitstream α => (Bool -> Bool) -> α -> α
- dropWhile :: Bitstream α => (Bool -> Bool) -> α -> α
- span :: Bitstream α => (Bool -> Bool) -> α -> (α, α)
- break :: Bitstream α => (Bool -> Bool) -> α -> (α, α)
- elem :: Bitstream α => Bool -> α -> Bool
- (∈) :: Bitstream α => Bool -> α -> Bool
- (∋) :: Bitstream α => α -> Bool -> Bool
- notElem :: Bitstream α => Bool -> α -> Bool
- (∉) :: Bitstream α => Bool -> α -> Bool
- (∌) :: Bitstream α => α -> Bool -> Bool
- find :: Bitstream α => (Bool -> Bool) -> α -> Maybe Bool
- filter :: Bitstream α => (Bool -> Bool) -> α -> α
- partition :: Bitstream α => (Bool -> Bool) -> α -> (α, α)
- (!!) :: (Bitstream α, Integral n) => α -> n -> Bool
- elemIndex :: (Bitstream α, Integral n) => Bool -> α -> Maybe n
- elemIndices :: (Bitstream α, Integral n) => Bool -> α -> [n]
- findIndex :: (Bitstream α, Integral n) => (Bool -> Bool) -> α -> Maybe n
- findIndices :: (Bitstream α, Integral n) => (Bool -> Bool) -> α -> [n]
- zip :: Bitstream α => α -> α -> [(Bool, Bool)]
- zip3 :: Bitstream α => α -> α -> α -> [(Bool, Bool, Bool)]
- zip4 :: Bitstream α => α -> α -> α -> α -> [(Bool, Bool, Bool, Bool)]
- zip5 :: Bitstream α => α -> α -> α -> α -> α -> [(Bool, Bool, Bool, Bool, Bool)]
- zip6 :: Bitstream α => α -> α -> α -> α -> α -> α -> [(Bool, Bool, Bool, Bool, Bool, Bool)]
- zipWith :: Bitstream α => (Bool -> Bool -> β) -> α -> α -> [β]
- zipWith3 :: Bitstream α => (Bool -> Bool -> Bool -> β) -> α -> α -> α -> [β]
- zipWith4 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> [β]
- zipWith5 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> [β]
- zipWith6 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> α -> [β]
- unzip :: Bitstream α => [(Bool, Bool)] -> (α, α)
- unzip3 :: Bitstream α => [(Bool, Bool, Bool)] -> (α, α, α)
- unzip4 :: Bitstream α => [(Bool, Bool, Bool, Bool)] -> (α, α, α, α)
- unzip5 :: Bitstream α => [(Bool, Bool, Bool, Bool, Bool)] -> (α, α, α, α, α)
- unzip6 :: Bitstream α => [(Bool, Bool, Bool, Bool, Bool, Bool)] -> (α, α, α, α, α, α)
- getContents :: Bitstream (Packet d) => IO (Bitstream d)
- putBits :: Bitstream (Packet d) => Bitstream d -> IO ()
- interact :: Bitstream (Packet d) => (Bitstream d -> Bitstream d) -> IO ()
- readFile :: Bitstream (Packet d) => FilePath -> IO (Bitstream d)
- writeFile :: Bitstream (Packet d) => FilePath -> Bitstream d -> IO ()
- appendFile :: Bitstream (Packet d) => FilePath -> Bitstream d -> IO ()
- hGetContents :: Bitstream (Packet d) => Handle -> IO (Bitstream d)
- hGet :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)
- hGetSome :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)
- hGetNonBlocking :: Bitstream (Packet d) => Handle -> Int -> IO (Bitstream d)
- hPut :: Bitstream (Packet d) => Handle -> Bitstream d -> IO ()
Types
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: and
Bitstream Left.
Bitstream Right
Instances
| Bitstream (Packet d) => Eq (Bitstream d) | |
| Bitstream (Packet d) => Ord (Bitstream d) |
let x = |
| Show (Packet d) => Show (Bitstream d) | |
| Bitstream (Packet d) => Monoid (Bitstream d) |
|
| Bitstream (Packet d) => Bitstream (Bitstream d) |
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]
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]
Introducing and eliminating Bitstreams
fromPackets :: Vector (Packet d) -> Bitstream dSource
Converting from/to strict ByteStrings
fromByteString :: ByteString -> Bitstream dSource
O(n) Convert a strict ByteString into a strict
Bitstream.
toByteString :: forall d. Bitstream (Packet d) => Bitstream d -> ByteStringSource
O(n) converts a strict toByteString bitsBitstream 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 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
requires the whole Stream BoolBitstream 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 Streamunstream$ Stream.tail $streambs
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.
Changing bit order in octets
directionLToR :: Bitstream Left -> Bitstream RightSource
O(n) Convert a into a Bitstream Left. Bit directions only affect octet-based operations such as
Bitstream
RighttoByteString.
directionRToL :: Bitstream Right -> Bitstream LeftSource
O(n) Convert a into a Bitstream Right. Bit directions only affect octet-based operations such as
Bitstream
LefttoByteString.
Basic interface
cons :: Bitstream α => Bool -> α -> αSource
strict: O(n), lazy: O(1) cons is an analogous to (:)
for lists.
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.
init :: Bitstream α => α -> αSource
O(n) Return all the bits of a Bitstream except the last
one. An exception will be thrown if empty.
Transforming Bitstreams
Reducing Bitstreams
Special folds
concatMap :: Bitstream α => (Bool -> α) -> α -> αSource
Map a function over a Bitstream and concatenate the results.
Building lists
Scans
Replication
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.
Substreams
Searching streams
Searching by equality
Searching with a predicate
Indexing streams
(!!) :: (Bitstream α, Integral n) => α -> n -> BoolSource
O(n) Bitstream index (subscript) operator, starting from 0.
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.
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
zipWith5 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> [β]Source
zipWith6 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> α -> [β]Source
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.
Files
readFile :: Bitstream (Packet d) => FilePath -> IO (Bitstream d)Source
O(n) Read an entire file strictly into a Bitstream.
writeFile :: Bitstream (Packet d) => FilePath -> Bitstream d -> IO ()Source
O(n) Write a Bitstream to a file.
appendFile :: 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) reads a hGet h nBitstream 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.
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.