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

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

Synthesizer.Generic.Filter.NonRecursive

Contents

Description

 

Synopsis

Envelope application

negate :: (C a, Transform sig a) => sig a -> sig aSource

amplify :: (C a, Transform sig a) => a -> sig a -> sig aSource

amplifyVector :: (C a v, Transform sig v) => a -> sig v -> sig vSource

envelopeSource

Arguments

:: (C a, Transform sig a) 
=> sig a

the envelope

-> sig a

the signal to be enveloped

-> sig a 

envelopeVectorSource

Arguments

:: (C a v, Read sig a, Transform sig v) 
=> sig a

the envelope

-> sig v

the signal to be enveloped

-> sig v 

fadeInOut :: (C a, Write sig a) => Int -> Int -> Int -> sig a -> sig aSource

Delay

delay :: (C y, Write sig y) => Int -> sig y -> sig ySource

delayPad :: Write sig y => y -> Int -> sig y -> sig ySource

delayPos :: (C y, Write sig y) => Int -> sig y -> sig ySource

delayNeg :: Transform sig y => Int -> sig y -> sig ySource

delayLazySize :: (C y, Write sig y) => LazySize -> Int -> sig y -> sig ySource

delayPadLazySize :: Write sig y => LazySize -> y -> Int -> sig y -> sig ySource

The pad value y must be defined, otherwise the chunk size of the padding can be observed.

delayPosLazySize :: (C y, Write sig y) => LazySize -> Int -> sig y -> sig ySource

smoothing

binomialMask :: (C a, Write sig a) => LazySize -> Int -> sig aSource

binomial :: (C a, C a, C a v, Transform sig v) => a -> a -> sig v -> sig vSource

ratioFreqToVariance :: C a => a -> a -> aSource

Compute the variance of the Gaussian such that its Fourier transform has value ratio at frequency freq.

binomial1 :: (C v, Transform sig v) => sig v -> sig vSource

sums :: (C v, Transform sig v) => Int -> sig v -> sig vSource

Moving (uniformly weighted) average in the most trivial form. This is very slow and needs about n * length x operations.

sumsDownsample2 :: (C v, Write sig v) => LazySize -> sig v -> sig vSource

downsample2 :: Write sig v => LazySize -> sig v -> sig vSource

downsample :: Write sig v => LazySize -> Int -> sig v -> sig vSource

sumRange :: (C v, Transform sig v) => sig v -> (Int, Int) -> vSource

pyramid :: (C v, Write sig v) => Int -> sig v -> ([Int], [sig v])Source

sumRangeFromPyramid :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> vSource

sumRangeFromPyramidReverse :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> vSource

sumRangeFromPyramidFoldr :: (C v, Transform sig v) => [sig v] -> (Int, Int) -> vSource

maybeAccumulateRangeFromPyramid :: Transform sig v => (v -> v -> v) -> [sig v] -> (Int, Int) -> Maybe vSource

consumeRangeFromPyramid :: Transform sig v => (v -> a -> a) -> a -> [sig v] -> (Int, Int) -> aSource

sumsPosModulated :: (C v, Transform sig (Int, Int), Transform sig v) => sig (Int, Int) -> sig v -> sig vSource

accumulatePosModulatedFromPyramid :: (Transform sig (Int, Int), Write sig v) => ([sig v] -> (Int, Int) -> v) -> ([Int], [sig v]) -> sig (Int, Int) -> sig vSource

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

The laziness granularity is 2^height.

sumsPosModulatedPyramid :: (C v, Transform sig (Int, Int), Write sig v) => Int -> sig (Int, Int) -> sig v -> sig vSource

withPaddedInput :: (Transform sig Int, Transform sig (Int, Int), Write sig y) => y -> (sig (Int, Int) -> sig y -> v) -> Int -> sig Int -> sig y -> vSource

movingAverageModulatedPyramid :: (C a, C a v, Transform sig Int, Transform sig (Int, Int), Write sig v) => a -> Int -> Int -> sig Int -> sig v -> sig 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.

inverseFrequencyModulationFloor :: (Ord t, C t, Write sig v, Read sig t) => LazySize -> sig t -> sig v -> sig vSource

Filter operators from calculus

differentiate :: (C v, Transform sig v) => sig v -> sig vSource

Forward difference quotient. Shortens the signal by one. Inverts run in the sense that differentiate (zero : integrate x) == x. The signal is shifted by a half time unit.

differentiateCenter :: (C v, Transform sig v) => sig v -> sig vSource

Central difference quotient. Shortens the signal by two elements, and shifts the signal by one element. (Which can be fixed by prepending an appropriate value.) For linear functions this will yield essentially the same result as differentiate. You obtain the result of differentiateCenter if you smooth the one of differentiate by averaging pairs of adjacent values.

ToDo: Vector variant

differentiate2 :: (C v, Transform sig v) => sig v -> sig vSource

Second derivative. It is differentiate2 == differentiate . differentiate but differentiate2 should be faster.

general non-recursive filters

generic :: (C a v, Transform sig a, Write sig v) => sig a -> sig v -> sig vSource

Unmodulated non-recursive filter (convolution)

Brute force implementation.

karatsubaFinite :: (C a, C b, C c, Transform sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig cSource

Both should signals should have similar length. If they have considerably different length, then better use karatsubaFiniteInfinite.

Implementation using Karatsuba trick and split-and-overlap-add. This way we stay in a ring, are faster than quadratic runtime but do not reach log-linear runtime.

karatsubaBounded :: (C a, C b, C c, Transform sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> T (sig a) -> T (sig b) -> T (sig c)Source

rechunk :: (Transform sig1 a, Transform sig1 b, Transform sig1 c, Transform sig0 c) => T (sig1 a) -> T (sig1 b) -> sig0 c -> sig1 cSource

karatsubaFiniteInfinite :: (C a, C b, C c, Transform sig a, Transform sig b, Transform sig c) => (a -> b -> c) -> sig a -> sig b -> sig cSource

The first operand must be finite and the second one can be infinite. For efficient operation we expect that the second signal is longer than the first one.

karatsubaInfinite :: (C a, C b, C c, Transform sig a, Transform sig c, Transform sig b) => (a -> b -> c) -> sig a -> sig b -> sig cSource

addShiftedSimple :: (C a, Transform sig a) => Int -> sig a -> sig a -> sig aSource

It must hold delay <= length a.

hard-wired convolutions for small sizes

type Pair a = (a, a)Source

convolvePair :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Pair b -> Triple cSource

Reasonable choices for the multiplication operation are '(*)', '(*>)', convolve.

sumAndConvolvePair :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Pair b -> ((a, b), Triple c)Source

type Triple a = (a, a, a)Source

convolvePairTriple :: (C a, C b, C c) => (a -> b -> c) -> Pair a -> Triple b -> (c, c, c, c)Source

convolveTriple :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> (c, c, c, c, c)Source

sumAndConvolveTriple :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> ((a, b), (c, c, c, c, c))Source

sumAndConvolveTripleAlt :: (C a, C b, C c) => (a -> b -> c) -> Triple a -> Triple b -> ((a, b), (c, c, c, c, c))Source

type Quadruple a = (a, a, a, a)Source

convolveQuadruple :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> (c, c, c, c, c, c, c)Source

sumAndConvolveQuadruple :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> ((a, b), (c, c, c, c, c, c, c))Source

sumAndConvolveQuadrupleAlt :: (C a, C b, C c) => (a -> b -> c) -> Quadruple a -> Quadruple b -> ((a, b), (c, c, c, c, c, c, c))Source