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

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

Synthesizer.Plain.Filter.Recursive.Universal

Description

State variable filter. One filter that generates lowpass, bandpass, highpass, bandlimit at once.

Synopsis

Documentation

data Parameter a

Constructors

Parameter 

Fields

k1 :: !a
 
k2 :: !a
 
ampIn :: !a
 
ampI1 :: !a
 
ampI2 :: !a
 
ampLimit :: !a
 

data Result a

Constructors

Result 

Fields

highpass :: !a
 
bandpass :: !a
 
lowpass :: !a
 
bandlimit :: !a
 

parameter :: C a => Pole a -> Parameter a

The computation of the internal parameters is a bit complicated, but it fulfills the following properties:

  • At the resonance frequency the band pass has 180 degree phase shift. This is also approximately the frequency where the filter has maximum output. Even more important, this is the frequency where the band limit filter works.
  • At the resonance frequency highpass, lowpass, and bandpass amplify by the factor resonance.
  • The lowpass amplifies the frequency zero by factor 1.
  • The highpass amplifies the highest representable (Nyquist) frequency by the factor 1.
  • The bandlimit amplifies both frequency zero and Nyquist frequency by factor one and cancels the resonance frequency.

parameterOld :: C a => Pole a -> Parameter a

The computation of the internal parameters is a bit complicated, but it fulfills the following properties:

  • At the resonance frequency the band pass has 180 degree phase shift. This is also approximately the frequency where the filter has maximum output. Even more important, this is the frequency where the band limit filter works.
  • At the resonance frequency highpass, lowpass, and bandpass amplify by the factor resonance.
  • The lowpass amplifies the frequency zero by factor 1.
  • The highpass amplifies the highest representable (Nyquist) frequency by the factor 1.
  • The bandlimit amplifies both frequency zero and Nyquist frequency by factor one and cancels the resonance frequency.

parameterAlt :: C a => Pole a -> Parameter a

The computation of the internal parameters is a bit complicated, but it fulfills the following properties:

  • At the resonance frequency the band pass has 180 degree phase shift. This is also approximately the frequency where the filter has maximum output. Even more important, this is the frequency where the band limit filter works.
  • At the resonance frequency highpass, lowpass, and bandpass amplify by the factor resonance.
  • The lowpass amplifies the frequency zero by factor 1.
  • The highpass amplifies the highest representable (Nyquist) frequency by the factor 1.
  • The bandlimit amplifies both frequency zero and Nyquist frequency by factor one and cancels the resonance frequency.

parameterToSecondOrderLowpass :: C a => Parameter a -> Parameter a

Convert parameters of universal filter to general second order filter parameters. Filtering with these parameters does not yield exactly the same result since the initial conditions are different.

type State v = (v, v)

step :: (C a, C a v) => Parameter a -> v -> State (State v) (Result v)

Universal filter: Computes high pass, band pass, low pass in one go

modifierInit :: (C a, C a v) => Initialized (State v) (v, v) (Parameter a) v (Result v)

modifier :: (C a, C a v) => Simple (State v) (Parameter a) v (Result v)

causal :: (C a, C a v) => T (Parameter a, v) (Result v)

runInit :: (C a, C a v) => (v, v) -> T (Parameter a) -> T v -> T (Result v)

run :: (C a, C a v) => T (Parameter a) -> T v -> T (Result v)