Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Bitstream.Generic
Contents
Description
Generic interface to diverse types of Bitstream
.
- class Bitstream α where
- basicStream :: α -> Stream Bool
- basicUnstream :: Stream Bool -> α
- basicCons :: Bool -> α -> α
- basicCons' :: Bool -> α -> α
- basicSnoc :: α -> Bool -> α
- basicAppend :: α -> α -> α
- basicTail :: α -> α
- basicInit :: α -> α
- basicMap :: (Bool -> Bool) -> α -> α
- basicReverse :: α -> α
- basicConcat :: [α] -> α
- basicScanl :: (Bool -> Bool -> Bool) -> Bool -> α -> α
- basicTake :: Integral n => n -> α -> α
- basicDrop :: Integral n => n -> α -> α
- basicTakeWhile :: (Bool -> Bool) -> α -> α
- basicDropWhile :: (Bool -> Bool) -> α -> α
- basicFilter :: (Bool -> Bool) -> α -> α
- basicPartition :: (Bool -> Bool) -> α -> (α, α)
- basicFromNBits :: (Integral n, Integral β, Bits β) => n -> β -> α
- basicToBits :: (Integral β, Bits β) => α -> β
- empty :: Bitstream α => α
- (∅) :: Bitstream α => α
- singleton :: Bitstream α => Bool -> α
- pack :: Bitstream α => [Bool] -> α
- unpack :: Bitstream α => α -> [Bool]
- fromBits :: (Integral β, FiniteBits β, Bitstream α) => β -> α
- fromNBits :: (Integral n, Integral β, Bits β, Bitstream α) => n -> β -> α
- toBits :: (Bitstream α, Integral β, Bits β) => α -> β
- stream :: Bitstream α => α -> Stream Bool
- unstream :: Bitstream α => Stream Bool -> α
- cons :: Bitstream α => Bool -> α -> α
- 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 :: (Integral n, Bitstream α) => n -> Bool -> α
- unfoldr :: Bitstream α => (β -> Maybe (Bool, β)) -> β -> α
- unfoldrN :: (Integral n, Bitstream α) => n -> (β -> Maybe (Bool, β)) -> β -> α
- take :: (Integral n, Bitstream α) => n -> α -> α
- drop :: (Integral n, Bitstream α) => 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, Show 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)] -> (α, α, α, α, α, α)
The type class
class Bitstream α where Source
Class of diverse types of Bitstream
.
Methods of this class are functions of Bitstream
s that are 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 basicCons'
,
basicConcat
, basicReplicate
, basicPartition
and
basicFromBits
.
Minimal complete definition
basicStream, basicUnstream, basicCons, basicSnoc, basicAppend, basicTail, basicInit, basicMap, basicReverse, basicScanl, basicTake, basicDrop, basicTakeWhile, basicDropWhile, basicFilter, basicFromNBits, basicToBits
Methods
basicStream :: α -> Stream Bool Source
basicUnstream :: Stream Bool -> α Source
basicCons :: Bool -> α -> α Source
basicCons' :: Bool -> α -> α Source
basicSnoc :: α -> Bool -> α Source
basicAppend :: α -> α -> α Source
basicMap :: (Bool -> Bool) -> α -> α Source
basicReverse :: α -> α Source
basicConcat :: [α] -> α Source
basicScanl :: (Bool -> Bool -> Bool) -> Bool -> α -> α Source
basicTake :: Integral n => n -> α -> α Source
basicDrop :: Integral n => n -> α -> α Source
basicTakeWhile :: (Bool -> Bool) -> α -> α Source
basicDropWhile :: (Bool -> Bool) -> α -> α Source
basicFilter :: (Bool -> Bool) -> α -> α Source
basicPartition :: (Bool -> Bool) -> α -> (α, α) Source
basicFromNBits :: (Integral n, Integral β, Bits β) => n -> β -> α Source
basicToBits :: (Integral β, Bits β) => α -> β Source
Introducing and eliminating Bitstream
s
Converting from/to Bits'
fromBits :: (Integral β, FiniteBits β, Bitstream α) => β -> α Source
O(n) Convert a FiniteBits
into a Bitstream
.
Converting from/to Stream
s
stream :: Bitstream α => α -> Stream Bool Source
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 Bitstream
s back from
requires the whole Stream
Bool
Bitstream
to be constructed from
scratch. Moreover, for lazy Bitstream
s this leads to be an
incorrect strictness behaviour because lazy Bitstream
s 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 $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
Bitstream
s.
The automatic fusion rules are carefully designed to fire only when there aren't any reason to preserve the original packet / chunk structure.
Basic interface
cons :: Bitstream α => Bool -> α -> α Source
strict: O(n), lazy: O(1) cons
is an analogous to (:
) for
lists.
cons' :: Bitstream α => Bool -> α -> α Source
O(n) For strict Bitstream
s, 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.
head :: Bitstream α => α -> Bool Source
O(1) Extract the first bit of a non-empty Bitstream
. An
exception will be thrown if empty.
last :: Bitstream α => α -> Bool Source
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.
length :: Bitstream α => Num n => α -> n Source
strict: O(1), lazy: O(n) Return the length of a finite
Bitstream
.
Transforming Bitstream
s
Reducing Bitstream
s
foldl1' :: Bitstream α => (Bool -> Bool -> Bool) -> α -> Bool Source
O(n) A strict version of foldl1
.
Special folds
concatMap :: Bitstream α => (Bool -> α) -> α -> α Source
Map a function over a Bitstream
and concatenate the results.
Building Bitstream
s
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
(∌) :: Bitstream α => α -> Bool -> Bool infix 4 Source
(∌) = flip
(∉)
U+220C, DOES NOT CONTAIN AS MEMBER
Searching with a predicate
Indexing streams
(!!) :: (Bitstream α, Integral n, Show n) => α -> n -> Bool infixl 9 Source
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