storablevector-0.2.13.2: Fast, packed, strict storable arrays with a list interface like ByteString
Safe HaskellSafe-Inferred
LanguageHaskell98

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

[____] [____] [____] [____] ...
  [__] [____] [____] [____] ...
    [] [____] [____] [____] ...
Synopsis

Documentation

data Vector a Source #

Instances

Instances details
(Storable a, Arbitrary a) => Arbitrary (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

arbitrary :: Gen (Vector a) #

shrink :: Vector a -> [Vector a] #

Storable a => Monoid (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Storable a => Semigroup (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

(<>) :: Vector a -> Vector a -> Vector a #

sconcat :: NonEmpty (Vector a) -> Vector a #

stimes :: Integral b => b -> Vector a -> Vector a #

(Storable a, Show a) => Show (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Storable a => NFData (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

rnf :: Vector a -> () #

(Storable a, Eq a) => Eq (Vector a) Source # 
Instance details

Defined in Data.StorableVector.Lazy

Methods

(==) :: Vector a -> Vector a -> Bool #

(/=) :: Vector a -> Vector a -> Bool #

data ChunkSize Source #

Instances

Instances details
Arbitrary ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Monoid ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Semigroup ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Num ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Show ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Eq ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

Ord ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

C ChunkSize Source # 
Instance details

Defined in Data.StorableVector.Lazy

pack :: Storable a => LazySize -> [a] -> Vector a Source #

unpack :: Storable a => Vector a -> [a] Source #

packWith :: Storable b => LazySize -> (a -> b) -> [a] -> Vector b Source #

unpackWith :: Storable a => (a -> b) -> Vector a -> [b] Source #

Warning: It seems to be used nowhere and might be removed.

unfoldrN :: Storable b => LazySize -> (a -> Maybe (b, a)) -> a -> (Vector b, Maybe a) Source #

iterateN :: Storable a => LazySize -> (a -> a) -> a -> Vector a Source #

cons :: Storable a => a -> Vector a -> Vector a Source #

append :: Storable a => Vector a -> Vector a -> Vector a infixr 5 Source #

concat :: Storable a => [Vector a] -> Vector a Source #

map :: (Storable x, Storable y) => (x -> y) -> Vector x -> Vector y Source #

foldl :: Storable b => (a -> b -> a) -> a -> Vector b -> a Source #

foldl' :: Storable b => (a -> b -> a) -> a -> Vector b -> a Source #

any :: Storable a => (a -> Bool) -> Vector a -> Bool Source #

all :: Storable a => (a -> Bool) -> Vector a -> Bool Source #

maximum :: (Storable a, Ord a) => Vector a -> a Source #

minimum :: (Storable a, Ord a) => Vector a -> a Source #

viewL :: Storable a => Vector a -> Maybe (a, Vector a) Source #

viewR :: Storable a => Vector a -> Maybe (Vector a, a) Source #

switchL :: Storable a => b -> (a -> Vector a -> b) -> Vector a -> b Source #

switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b Source #

scanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a 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 y Source #

take :: Storable a => LazySize -> Vector a -> Vector a Source #

Generates laziness breaks wherever either the lazy length number or the vector has a chunk boundary.

takeVectorPattern :: Storable a => LazySize -> Vector a -> Vector a Source #

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.

dropWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a Source #

takeWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a Source #

span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

filter :: Storable a => (a -> Bool) -> Vector a -> Vector a Source #

zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

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 d Source #

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 Source #

zipWithSize :: (Storable a, Storable b, Storable c) => LazySize -> (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

zipWithSize3 :: (Storable a, Storable b, Storable c, Storable d) => LazySize -> (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

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 Source #