synthesizer-core-0.4.0.4: Audio signal processing coded in Haskell: Low level part

Portabilityrequires multi-parameter type classes
Stabilityprovisional
Maintainersynthesizer@henning-thielemann.de

Synthesizer.Storable.Filter.NonRecursive

Description

 

Synopsis

Documentation

accumulateDownsample2Strict :: Storable v => (v -> v -> v) -> Maybe v -> Vector v -> (Maybe v, Vector v)Source

The Maybe type carries an unpaired value from one block to the next one.

accumulateDownsample2 :: Storable v => (v -> v -> v) -> T v -> T vSource

sumsDownsample2 :: (C v, Storable v) => T v -> T vSource

sumsDownsample2Alt :: (C v, Storable v) => T v -> T vSource

convolveDownsample2 :: (C a v, Storable a, Storable v) => T a -> T v -> T vSource

downsample2Strict :: Storable v => Int -> Vector v -> Vector vSource

offset must be zero or one.

downsample2 :: Storable v => T v -> T vSource

pyramid :: Storable v => (v -> v -> v) -> Int -> T v -> [T v]Source

accumulatePosModulatedPyramid :: Storable v => ([T v] -> (Int, Int) -> v) -> ([Int], [T v]) -> T (Int, Int) -> T vSource

Moving average, where window bounds must be always non-negative.

The laziness granularity is 2^height.

This function is only slightly more efficient than its counterpart from Generic.Filter, since it generates strict blocks and not one-block chunky signals.

sumsPosModulatedPyramid :: (C v, Storable v) => Int -> T (Int, Int) -> T v -> T vSource

accumulateBinPosModulatedPyramid :: Storable v => (v -> v -> v) -> Int -> T (Int, Int) -> T v -> T vSource

movingAverageModulatedPyramid :: (C a, C a v, Storable Int, Storable v) => a -> Int -> Int -> T Int -> T v -> T vSource

The first argument is the amplification. The main reason to introduce it, was to have only a Module constraint instead of Field. This way we can also filter stereo signals.

movingAccumulateModulatedPyramid :: Storable v => (v -> v -> v) -> v -> Int -> Int -> T Int -> T v -> T vSource

inverseFrequencyModulationFloor :: (Storable v, Read sig t, C t, Ord t) => ChunkSize -> sig t -> T v -> T vSource

The function is like that of Synthesizer.State.Filter.NonRecursive.inverseFrequencyModulationFloor, but this function preserves in a sense the chunk structure.

The result will have laziness breaks at least at the chunk boundaries that correspond to the breaks in the input signal. However we insert more breaks, such that a maximum chunk size can be warrented. (Since control and input signal are aligned in time, we might as well use the control chunk structure. Currently I do not know what is better. For the above example it doesn't matter.)

This function cannot be written using generic functions, since we have to inspect the chunks individually.

inverseFrequencyModulationChunk :: (Storable v, C t, Ord t) => ChunkSize -> (s -> Maybe (t, s)) -> (t, s) -> Vector v -> (T v, Maybe (t, s))Source