Chunky signal stream build on StorableVector.
Hints for fusion: - Higher order functions should always be inlined in the end in order to turn them into machine loops instead of calling a function in an inner loop.
- type T = Vector
- hPut :: Storable a => Handle -> Vector a -> IO ()
- data ChunkSize
- chunkSize :: Int -> ChunkSize
- defaultChunkSize :: ChunkSize
- scanL :: (Storable a, Storable b) => (a -> b -> a) -> a -> T b -> T a
- map :: (Storable x, Storable y) => (x -> y) -> Vector x -> Vector y
- iterate :: Storable a => ChunkSize -> (a -> a) -> a -> Vector a
- zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
- append :: Storable a => Vector a -> Vector a -> Vector a
- concat :: Storable a => [Vector a] -> Vector a
- span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- splitAt :: Storable a => Int -> Vector a -> (Vector a, Vector 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
- unfoldr :: Storable b => ChunkSize -> (a -> Maybe (b, a)) -> a -> Vector b
- reverse :: Storable a => Vector a -> Vector a
- crochetL :: (Storable x, Storable y) => (x -> acc -> Maybe (y, acc)) -> acc -> Vector x -> Vector y
- writeFile :: Storable a => FilePath -> Vector a -> IO ()
- mix :: (C x, Storable x) => T x -> T x -> T x
- mixSndPattern :: (C x, Storable x) => T x -> T x -> T x
- mixSize :: (C x, Storable x) => ChunkSize -> T x -> T x -> T x
- splitAtPad :: (C x, Storable x) => ChunkSize -> Int -> T x -> (T x, T x)
- null :: Storable a => Vector a -> Bool
- fromChunks :: Storable a => [Vector a] -> Vector a
- foldr :: Storable b => (b -> a -> a) -> a -> Vector b -> a
- delay :: Storable y => ChunkSize -> y -> Int -> T y -> T y
- delayLoop :: Storable y => (T y -> T y) -> T y -> T y
- delayLoopOverlap :: (C y, Storable y) => Int -> (T y -> T y) -> T y -> T y
- empty :: Storable a => Vector a
- cons :: Storable a => a -> Vector a -> Vector a
- replicate :: Storable a => ChunkSize -> Int -> a -> Vector a
- repeat :: Storable a => ChunkSize -> a -> Vector a
- drop :: Storable a => Int -> Vector a -> Vector a
- take :: Storable a => Int -> Vector a -> Vector a
- takeCrochet :: Storable a => Int -> T a -> T a
- fromList :: Storable a => ChunkSize -> [a] -> T a
- zipWithRest :: (Storable c, Storable x) => (x -> x -> c) -> T x -> T x -> (Vector c, (Bool, T x))
- zipWithAppend :: Storable x => (x -> x -> x) -> T x -> T x -> T x
- switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b
- toList :: Storable a => T a -> [a]
- chunks :: Vector a -> [Vector a]
- genericLength :: C i => T x -> i
Documentation
data ChunkSize
zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
Generates laziness breaks wherever one of the input signals has a chunk boundary.
mix :: (C x, Storable x) => T x -> T x -> T xSource
This implementation generates laziness breaks whereever one of the original sequences has laziness breaks. It should be commutative in this respect.
It is more efficient than mixSize
since it appends the rest of the longer signal without copying.
mixSndPattern :: (C x, Storable x) => T x -> T x -> T xSource
Mix while maintaining the pattern of the second operand. This is closer to the behavior of Vector.zipWithLastPattern.
fromChunks :: Storable a => [Vector a] -> Vector a
:: (C y, Storable y) | |
=> Int | |
-> (T y -> T y) | Processor that shall be run in a feedback loop.
It's absolutely necessary that this function preserves the chunk structure
and that it does not look a chunk ahead.
That's guaranteed for processes that do not look ahead at all,
like |
-> T y | input |
-> T y | output has the same length as the input |
zipWithRest :: (Storable c, Storable x) => (x -> x -> c) -> T x -> T x -> (Vector c, (Bool, T x))Source
genericLength :: C i => T x -> iSource