synthesizer-core-0.8.3: Audio signal processing coded in Haskell: Low level part
Copyright(c) Henning Thielemann 2008-2012
LicenseGPL
Maintainersynthesizer@henning-thielemann.de
Stabilityprovisional
Portabilityrequires multi-parameter type classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Synthesizer.Plain.Filter.Recursive.Universal

Description

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

Synopsis

Documentation

data Parameter a Source #

Constructors

Parameter 

Fields

Instances

Instances details
Foldable Parameter Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

fold :: Monoid m => Parameter m -> m #

foldMap :: Monoid m => (a -> m) -> Parameter a -> m #

foldMap' :: Monoid m => (a -> m) -> Parameter a -> m #

foldr :: (a -> b -> b) -> b -> Parameter a -> b #

foldr' :: (a -> b -> b) -> b -> Parameter a -> b #

foldl :: (b -> a -> b) -> b -> Parameter a -> b #

foldl' :: (b -> a -> b) -> b -> Parameter a -> b #

foldr1 :: (a -> a -> a) -> Parameter a -> a #

foldl1 :: (a -> a -> a) -> Parameter a -> a #

toList :: Parameter a -> [a] #

null :: Parameter a -> Bool #

length :: Parameter a -> Int #

elem :: Eq a => a -> Parameter a -> Bool #

maximum :: Ord a => Parameter a -> a #

minimum :: Ord a => Parameter a -> a #

sum :: Num a => Parameter a -> a #

product :: Num a => Parameter a -> a #

Traversable Parameter Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

traverse :: Applicative f => (a -> f b) -> Parameter a -> f (Parameter b) #

sequenceA :: Applicative f => Parameter (f a) -> f (Parameter a) #

mapM :: Monad m => (a -> m b) -> Parameter a -> m (Parameter b) #

sequence :: Monad m => Parameter (m a) -> m (Parameter a) #

Applicative Parameter Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

pure :: a -> Parameter a #

(<*>) :: Parameter (a -> b) -> Parameter a -> Parameter b #

liftA2 :: (a -> b -> c) -> Parameter a -> Parameter b -> Parameter c #

(*>) :: Parameter a -> Parameter b -> Parameter b #

(<*) :: Parameter a -> Parameter b -> Parameter a #

Functor Parameter Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

fmap :: (a -> b) -> Parameter a -> Parameter b #

(<$) :: a -> Parameter b -> Parameter a #

C a v => C a (Parameter v) Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Storable a => Storable (Parameter a) Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

sizeOf :: Parameter a -> Int #

alignment :: Parameter a -> Int #

peekElemOff :: Ptr (Parameter a) -> Int -> IO (Parameter a) #

pokeElemOff :: Ptr (Parameter a) -> Int -> Parameter a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Parameter a) #

pokeByteOff :: Ptr b -> Int -> Parameter a -> IO () #

peek :: Ptr (Parameter a) -> IO (Parameter a) #

poke :: Ptr (Parameter a) -> Parameter a -> IO () #

data Result a Source #

Constructors

Result 

Instances

Instances details
Foldable Result Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldMap' :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Applicative Result Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Functor Result Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

C a v => C a (Result v) Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

(*>) :: a -> Result v -> Result v #

Storable a => Storable (Result a) Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

sizeOf :: Result a -> Int #

alignment :: Result a -> Int #

peekElemOff :: Ptr (Result a) -> Int -> IO (Result a) #

pokeElemOff :: Ptr (Result a) -> Int -> Result a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Result a) #

pokeByteOff :: Ptr b -> Int -> Result a -> IO () #

peek :: Ptr (Result a) -> IO (Result a) #

poke :: Ptr (Result a) -> Result a -> IO () #

C v => C (Result v) Source # 
Instance details

Defined in Synthesizer.Plain.Filter.Recursive.Universal

Methods

zero :: Result v #

(+) :: Result v -> Result v -> Result v #

(-) :: Result v -> Result v -> Result v #

negate :: Result v -> Result v #

type State v = (v, v) Source #

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

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

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

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

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 Source #

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.

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

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

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

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

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

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 Source #

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.