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

Copyright(c) Henning Thielemann 2008-2011
LicenseGPL
Maintainersynthesizer@henning-thielemann.de
Stabilityprovisional
Portabilityrequires multi-parameter type classes
Safe HaskellNone
LanguageHaskell2010

Synthesizer.Generic.Filter.NonRecursive

Contents

Description

 

Synopsis

Envelope application

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

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

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

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

envelope

Arguments

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

the envelope

-> sig a

the signal to be enveloped

-> sig a 

envelopeVector

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 a

Delay

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

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

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

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

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

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

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 y

smoothing

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

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

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

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 v

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

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 v

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

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

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

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

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

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

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

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

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

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

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

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 v

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

movingAverageModulatedPyramid :: (C a, C a v, Transform sig Int, Transform sig (Int, Int), Write sig v) => a -> Int -> Int -> sig Int -> sig v -> sig v

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 v

Filter operators from calculus

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

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 v

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 v

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 v

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 c

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)

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

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

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 c

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

It must hold delay <= length a.

hard-wired convolutions for small sizes

type Pair a = (a, a)

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

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)

type Triple a = (a, a, a)

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

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

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

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

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

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

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

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