Data.Bitstream.Generic
Description
Generic interface to diverse types of Bitstream.
- class Bitstream α where
- stream :: α -> Stream Bool
- unstream :: Stream Bool -> α
- cons :: Bool -> α -> α
- cons' :: Bool -> α -> α
- snoc :: α -> Bool -> α
- append :: α -> α -> α
- tail :: α -> α
- init :: α -> α
- map :: (Bool -> Bool) -> α -> α
- reverse :: α -> α
- concat :: [α] -> α
- scanl :: (Bool -> Bool -> Bool) -> Bool -> α -> α
- replicate :: Integral n => n -> Bool -> α
- take :: Integral n => n -> α -> α
- drop :: Integral n => n -> α -> α
- takeWhile :: (Bool -> Bool) -> α -> α
- dropWhile :: (Bool -> Bool) -> α -> α
- filter :: (Bool -> Bool) -> α -> α
- partition :: (Bool -> Bool) -> α -> (α, α)
- pack :: Bitstream α => [Bool] -> α
- unpack :: Bitstream α => α -> [Bool]
- empty :: Bitstream α => α
- singleton :: Bitstream α => Bool -> α
- head :: Bitstream α => α -> Bool
- last :: Bitstream α => α -> Bool
- null :: Bitstream α => α -> Bool
- length :: Bitstream α => Num n => α -> n
- concatMap :: Bitstream α => (Bool -> α) -> α -> α
- 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
- and :: Bitstream α => α -> Bool
- or :: Bitstream α => α -> Bool
- any :: Bitstream α => (Bool -> Bool) -> α -> Bool
- all :: Bitstream α => (Bool -> Bool) -> α -> Bool
- unfoldr :: Bitstream α => (β -> Maybe (Bool, β)) -> β -> α
- unfoldrN :: (Bitstream α, Integral n) => n -> (β -> Maybe (Bool, β)) -> β -> α
- scanl1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> α
- scanr :: Bitstream α => (Bool -> Bool -> Bool) -> Bool -> α -> α
- scanr1 :: Bitstream α => (Bool -> Bool -> Bool) -> α -> α
- span :: Bitstream α => (Bool -> Bool) -> α -> (α, α)
- break :: Bitstream α => (Bool -> Bool) -> α -> (α, α)
- elem :: Bitstream α => Bool -> α -> Bool
- notElem :: Bitstream α => Bool -> α -> Bool
- find :: Bitstream α => (Bool -> Bool) -> α -> Maybe 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)] -> (α, α, α, α, α, α)
- (∅) :: Bitstream α => α
- (⧺) :: Bitstream α => α -> α -> α
- (∈) :: Bitstream α => Bool -> α -> Bool
- (∋) :: Bitstream α => α -> Bool -> Bool
- (∉) :: Bitstream α => Bool -> α -> Bool
- (∌) :: Bitstream α => α -> Bool -> Bool
Documentation
Class of diverse types of Bitstream.
Methods of this class are functions of Bitstreams that is either
basic functions to implement other ones, or have to preserve their
packet/chunk structure for efficiency and strictness behaviour.
Minimum complete implementation: All but cons', concat,
replicate and partition.
Methods
stream :: α -> 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.
unstream :: Stream Bool -> αSource
strict: O(n), lazy: O(1) cons is an analogous to (:)
for lists.
O(n) For strict Bitstreams, cons' is exactly the same
as cons.
For lazy ones, cons' is strict in the Bitstream we are
consing onto. More precisely, it forces the first chunk to be
evaluated. It does this because, for space efficiency, it may
coalesce the new bit onto the first chunk rather than starting
a new chunk.
O(n) Append a bit to the end of a Bitstream.
O(n) Append two Bitstreams.
O(1) Extract the bits after the head of a non-empty
Bitstream. An exception will be thrown if empty.
O(n) Return all the bits of a Bitstream except the last
one. An exception will be thrown if empty.
map :: (Bool -> Bool) -> α -> αSource
O(n) Map a function over a Bitstream.
O(n) Reverse a Bitstream.
O(n) Concatenate all Bitstreams in the list.
scanl :: (Bool -> Bool -> Bool) -> Bool -> α -> αSource
O(n) scanl is similar to foldl, but returns a
Bitstream of successive reduced bits from the left:
scanlf z [x1, x2, ...] == [z, zfx1, (zfx1)fx2, ...]
Note that
last(scanlf z xs) ==foldlf z xs
replicate :: Integral n => n -> Bool -> αSource
take :: Integral n => 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 => n -> α -> αSource
takeWhile :: (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 :: (Bool -> Bool) -> α -> αSource
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.
concatMap :: Bitstream α => (Bool -> α) -> α -> αSource
Map a function over a Bitstream and concatenate the results.
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.
(!!) :: (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.
zipWith5 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> [β]Source
zipWith6 :: Bitstream α => (Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> β) -> α -> α -> α -> α -> α -> α -> [β]Source