Safe Haskell | None |
---|
Data.StorableVector.Lazy.Pattern
Description
Functions for StorableVector
that allow control of the size of individual chunks.
This is import for an application like the following: You want to mix audio signals that are relatively shifted. The structure of chunks of three streams may be illustrated as:
[____] [____] [____] [____] ... [____] [____] [____] [____] ... [____] [____] [____] [____] ...
When we mix the streams (zipWith3 (x y z -> x+y+z)
)
with respect to the chunk structure of the first signal,
computing the first chunk requires full evaluation of all leading chunks of the stream.
However the last value of the third leading chunk
is much later in time than the last value of the first leading chunk.
We like to reduce these dependencies using a different chunk structure,
say
[____] [____] [____] [____] ... [__] [____] [____] [____] ... [] [____] [____] [____] ...
- data Vector a
- data ChunkSize
- chunkSize :: Int -> ChunkSize
- defaultChunkSize :: ChunkSize
- type LazySize = T ChunkSize
- empty :: Storable a => Vector a
- singleton :: Storable a => a -> Vector a
- pack :: Storable a => LazySize -> [a] -> Vector a
- unpack :: Storable a => Vector a -> [a]
- packWith :: Storable b => LazySize -> (a -> b) -> [a] -> Vector b
- unpackWith :: Storable a => (a -> b) -> Vector a -> [b]
- unfoldrN :: Storable b => LazySize -> (a -> Maybe (b, a)) -> a -> (Vector b, Maybe a)
- iterateN :: Storable a => LazySize -> (a -> a) -> a -> Vector a
- cycle :: Storable a => Vector a -> Vector a
- replicate :: Storable a => LazySize -> a -> Vector a
- null :: Storable a => Vector a -> Bool
- length :: Vector a -> LazySize
- cons :: Storable a => a -> Vector a -> Vector a
- append :: Storable a => Vector a -> Vector a -> Vector a
- concat :: Storable a => [Vector a] -> Vector a
- map :: (Storable x, Storable y) => (x -> y) -> Vector x -> Vector y
- reverse :: Storable a => Vector a -> Vector a
- foldl :: Storable b => (a -> b -> a) -> a -> Vector b -> a
- foldl' :: Storable b => (a -> b -> a) -> a -> Vector b -> a
- any :: Storable a => (a -> Bool) -> Vector a -> Bool
- all :: Storable a => (a -> Bool) -> Vector a -> Bool
- maximum :: (Storable a, Ord a) => Vector a -> a
- minimum :: (Storable a, Ord a) => Vector a -> a
- viewL :: Storable a => Vector a -> Maybe (a, Vector a)
- viewR :: Storable a => Vector a -> Maybe (Vector a, a)
- switchL :: Storable a => b -> (a -> Vector a -> b) -> Vector a -> b
- switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b
- scanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
- mapAccumL :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
- mapAccumR :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
- crochetL :: (Storable x, Storable y) => (x -> acc -> Maybe (y, acc)) -> acc -> Vector x -> Vector y
- take :: Storable a => LazySize -> Vector a -> Vector a
- drop :: Storable a => LazySize -> Vector a -> Vector a
- splitAt :: Storable a => LazySize -> Vector a -> (Vector a, Vector a)
- takeVectorPattern :: Storable a => LazySize -> Vector a -> Vector a
- splitAtVectorPattern :: Storable a => LazySize -> Vector a -> (Vector a, Vector a)
- dropMarginRem :: Storable a => Int -> Int -> Vector a -> (Int, Vector a)
- dropMargin :: Storable a => Int -> Int -> Vector a -> Vector a
- dropWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
- takeWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
- span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- filter :: Storable a => (a -> Bool) -> Vector a -> Vector a
- zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
- zipWith3 :: (Storable a, Storable b, Storable c, Storable d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
- zipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
- zipWithSize :: (Storable a, Storable b, Storable c) => LazySize -> (a -> b -> c) -> Vector a -> Vector b -> Vector c
- zipWithSize3 :: (Storable a, Storable b, Storable c, Storable d) => LazySize -> (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
- zipWithSize4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => LazySize -> (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
Documentation
unpackWith :: Storable a => (a -> b) -> Vector a -> [b]Source
mapAccumL :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)Source
mapAccumR :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)Source
crochetL :: (Storable x, Storable y) => (x -> acc -> Maybe (y, acc)) -> acc -> Vector x -> Vector ySource
take :: Storable a => LazySize -> Vector a -> Vector aSource
Generates laziness breaks wherever either the lazy length number or the vector has a chunk boundary.
takeVectorPattern :: Storable a => LazySize -> Vector a -> Vector aSource
Preserves the chunk pattern of the lazy vector.
dropMarginRem :: Storable a => Int -> Int -> Vector a -> (Int, Vector a)Source
dropMarginRem n m xs
drops at most the first m
elements of xs
and ensures that xs
still contains n
elements.
Additionally returns the number of elements that could not be dropped
due to the margin constraint.
That is dropMarginRem n m xs == (k,ys)
implies length xs - m == length ys - k
.
Requires length xs >= n
.
zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector cSource
Generates laziness breaks wherever one of the input signals has a chunk boundary.
zipWith3 :: (Storable a, Storable b, Storable c, Storable d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector dSource
zipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector eSource
zipWithSize :: (Storable a, Storable b, Storable c) => LazySize -> (a -> b -> c) -> Vector a -> Vector b -> Vector cSource