synthesizer-dimensional-0.8.1.1: Audio signal processing with static physical dimensions
Copyright(c) Henning Thielemann 2008-2011
LicenseGPL
Maintainersynthesizer@henning-thielemann.de
Stabilityprovisional
Portabilityrequires multi-parameter type classes (Flat)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Synthesizer.Dimensional.Causal.ControlledProcess

Description

Basic definitions for causal signal processors that are controlled by another signal. E.g. a Moog lowpass filter is controlled by the cut-off frequency and the resonance. However internally the Moog filter uses some feed-back factors. The translation from cut-off frequency and resonance (we call them external parameters) to the feed-back factors (we call them internal parameters) depends on the sampling rate. The problem we want to tackle is, that computation of internal filter parameters is expensive, but application of filters is not. Thus we wish to compute internal filter parameters at a lower rate than the sampling rate of the input and output (refered to as audio rate, here).

Other digital sound synthesis systems solve it this way:

  • Csound, SuperCollider: They distinguish between audio rate (say 44100 Hz), control rate (say 4410 Hz) and note rate (irregular, but usually less then 100 Hz). The control rate is globally equal and constant.
  • ChucK: It updates internal filter parameters when external filter parameters change, that is, it updates by demand. In terms of control rates this means, that multiple control rates exist and they can be irregular.

After playing around with several approaches in this library, the following one appeals me most: We reveal the existence of internal filter parameters to the user, but we hide the details of that parameters. For every filter, we provide two functions: One that computes internal filter parameters from external ones and one for actual filtering of the audio data. We provide a type class that selects a filter according to the type of the internal filter parameters. That is, the user only has to choose a filter parameter computation, as found in Synthesizer.Dimensional.Causal.FilterParameter. For globally constant filter parameters, such as the filter order, we use the signal amplitude. You might call this abuse, but in future we may revise the notion of amplitude to that of a global signal parameter.

Additionally we provide functions that perform the full filtering process given only the filter parameter generator. There are two modes:

  • Synchronous: The filter parameters are computed at audio rate.
  • Asynchronous: The filter parameters are computed at a rate that can differ from audio rate. You can choose the control rate individually for every filter application.

This approach has several advantages:

  • A filter only has to treat inputs of the same sampling rate. We do not have to duplicate the code for coping with input at rates different from the sample rate.
  • We can provide different ways of specifying filter parameters, e.g. the resonance of a lowpass filter can be controlled either by the slope or by the amplification of the resonant frequency.
  • We can use different control rates in the same program.
  • We can even adapt the speed of filter parameter generation to the speed of changes in the control signal.
  • For a sinusoidal controlled filter sweep we can setup a table of filter parameters for logarithmically equally spaced cut-off frequencies and traverse this table at varying rates according to arcus sine.
  • Classical handling of control rate filter parameter computation can be considered as resampling of filter parameters with constant interpolation. If there is only a small number of internal filter parameters then we may resample with linear interpolation of the filter parameters.
Synopsis

Documentation

class C global => C global parameter a b | global parameter a -> b, global parameter b -> a where Source #

Select a filter process according to the filter parameter type.

Methods

process :: C u => T s u t (T s (T global (RateDep s parameter), a) b) Source #

Instances

Instances details
C q yv => C AllpassCascadeGlobal (Parameter q) (T amp yv) (T amp yv) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T AllpassCascadeGlobal (RateDep s (Parameter q)), T amp yv) (T amp yv)) Source #

C q yv => C FirstOrderGlobal (Parameter q) (T amp yv) (T amp (Result yv)) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T FirstOrderGlobal (RateDep s (Parameter q)), T amp yv) (T amp (Result yv))) Source #

C q yv => C MoogLowpassGlobal (Parameter q) (T amp yv) (T amp yv) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T MoogLowpassGlobal (RateDep s (Parameter q)), T amp yv) (T amp yv)) Source #

(Storable q, Storable yv, C q yv) => C SecondOrderCascadeGlobal (Parameter q) (T amp yv) (T amp yv) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T SecondOrderCascadeGlobal (RateDep s (Parameter q)), T amp yv) (T amp yv)) Source #

C q yv => C UniversalGlobal (Parameter q) (T amp yv) (T amp (Result yv)) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T UniversalGlobal (RateDep s (Parameter q)), T amp yv) (T amp (Result yv))) Source #

C q yv => C AllpassPhaserGlobal (q, Parameter q) (T amp yv) (T amp yv) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.FilterParameter

Methods

process :: C u => T0 s u t (T1 s (T AllpassPhaserGlobal (RateDep s (q, Parameter q)), T amp yv) (T amp yv)) Source #

newtype RateDep s ic Source #

This type tags an internal filter parameter with the sampling rate for which it was generated. Be aware, that in asynchronous application the internal filter parameters are computed at control rate, but the internal filter parameters must correspond to the sampling rate of the target audio signal. The type parameter s corresponds to that target audio rate.

Constructors

RateDep 

Fields

Instances

Instances details
C a ic => C a (RateDep s ic) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.ControlledProcess

Methods

scaleAndAccumulate :: (a, RateDep s ic) -> (RateDep s ic, RateDep s ic -> RateDep s ic) #

Storable ic => Storable (RateDep s ic) Source # 
Instance details

Defined in Synthesizer.Dimensional.Causal.ControlledProcess

Methods

sizeOf :: RateDep s ic -> Int #

alignment :: RateDep s ic -> Int #

peekElemOff :: Ptr (RateDep s ic) -> Int -> IO (RateDep s ic) #

pokeElemOff :: Ptr (RateDep s ic) -> Int -> RateDep s ic -> IO () #

peekByteOff :: Ptr b -> Int -> IO (RateDep s ic) #

pokeByteOff :: Ptr b -> Int -> RateDep s ic -> IO () #

peek :: Ptr (RateDep s ic) -> IO (RateDep s ic) #

poke :: Ptr (RateDep s ic) -> RateDep s ic -> IO () #

runSynchronous1 :: (C global parameter sampleIn sampleOut, C u, C ecAmp) => T s u t (T (T ecAmp ec) (T global (RateDep s parameter))) -> T s u t (Signal s ecAmp ec -> T s sampleIn sampleOut) Source #

runSynchronous2 :: (C global parameter sampleIn sampleOut, C u, C ecAmp0, C ecAmp1) => T s u t (T (T ecAmp0 ec0, T ecAmp1 ec1) (T global (RateDep s parameter))) -> T s u t (Signal s ecAmp0 ec0 -> Signal s ecAmp1 ec1 -> T s sampleIn sampleOut) Source #

runAsynchronous1 :: (C global ic sampleIn sampleOut, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp ec) (T global (RateDep s ic))) -> T (Dimensional u t) ecAmp (T ec) -> T s u t (T s sampleIn sampleOut) Source #

runAsynchronousBuffered1 :: (C global ic sampleIn sampleOut, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp ec) (T global (RateDep s ic))) -> T (Dimensional u t) ecAmp (T ec) -> T s u t (T s sampleIn sampleOut) Source #

processAsynchronous1 :: (C global ic sampleIn sampleOut, C ecAmp, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp ec) (T global (RateDep s ic))) -> T (Recip u) t -> (forall r. T r u t (Signal r ecAmp ec)) -> T s u t (T s sampleIn sampleOut) Source #

runAsynchronous2 :: (C global ic sampleIn sampleOut, C ecAmp0, C ecAmp1, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp0 ec0, T ecAmp1 ec1) (T global (RateDep s ic))) -> T (Dimensional u t) ecAmp0 (T ec0) -> T (Dimensional u t) ecAmp1 (T ec1) -> T s u t (T s sampleIn sampleOut) Source #

Using two SigP.T's as input has the disadvantage that their rates must be compared dynamically. It is not possible with our data structures to use one rate for multiple signals. We could also allow the input of a Rate.T and two Proc.T's, since this is the form we get from the computation routines. But this way we lose sharing.

processAsynchronous2 :: (C global ic sampleIn sampleOut, C ecAmp0, C ecAmp1, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp0 ec0, T ecAmp1 ec1) (T global (RateDep s ic))) -> T (Recip u) t -> (forall r. T r u t (Signal r ecAmp0 ec0)) -> (forall r. T r u t (Signal r ecAmp1 ec1)) -> T s u t (T s sampleIn sampleOut) Source #

This function will be more commonly used than runAsynchronous2, but it disallows sharing of control signals. It can be easily defined in terms of runAsynchronous2 and render, but the implementation here does not need the check for equal sample rates.

processAsynchronousBuffered2 :: (C global ic sampleIn sampleOut, C ecAmp0, C ecAmp1, C u, C t) => T t (RateDep s ic) -> T s u t (T (T ecAmp0 ec0, T ecAmp1 ec1) (T global (RateDep s ic))) -> T (Recip u) t -> (forall r. T r u t (Signal r ecAmp0 ec0)) -> (forall r. T r u t (Signal r ecAmp1 ec1)) -> T s u t (T s sampleIn sampleOut) Source #

This buffers internal control parameters before interpolation. This should be faster, since interpolation needs frequent look-ahead, and this is faster on a buffered signal than on a plain stateful signal generator.

Since the look-ahead is constant, it is interesting whether interpolation can be made more efficient without the inefficient intermediate list structure.