synthesizer-dimensional-0.5: Audio signal processing with static physical dimensions

Portabilityrequires multi-parameter type classes (Flat)
Stabilityprovisional
Maintainersynthesizer@henning-thielemann.de

Synthesizer.Dimensional.Causal.ControlledProcess

Description

Basic definitions for causal signal processors which are controlled by another signal. Additionally to Synthesizer.Dimensional.ControlledProcess you can convert those processes to plain causal processes in the case of equal audio and control rates (synchronous control).

It is sensible to bundle the functions computation of internal parameters and running the main process, since computation of the internal parameters depends on the sample rate of the main process in case of frequency control values even though the computation of internal parameters happens at a different sample rate.

ToDo: - Is it better to provide the conversion method not by a record but by a type class? The difficulty with this is, how to handle global parameters like the filter order? - Note, that parameters might be computed by different ways. Thus a type class with functional dependencies for automatic selection of input types and conversion will not always be flexible enough. - Is it possible and reasonable to hide the type parameter for the internal control parameter since the user does not need to know it? - The internal parameters that the converter generates usually depend on the sample rate of the (target) audio signal. However, it does not depend on the sample rate of control signal where it is applied to. How can we ensure that it is not used somewhere else? We could discourage access to it at all. But it might be sensible to define new external parameters in terms of existing ones. We could add a phantom s type parameter to internal control parameters. Would this do the trick? Is this convenient? See RateDep.

Synopsis

Documentation

data T conv proc Source

This is quite analogous to Dimensional.Causal.Process but adds the conv parameter for conversion from intuitive external parameters to internal parameters.

Constructors

Cons 

Fields

converter :: conv
 
processor :: proc
 

Instances

Functor (T conv)

The Functor instance allows to define an allpass phaser as ControlledProcess, reusing the allpass cascade provided as ControlledProcess. It is also possible to define a lowpass filter with resonance as ControlledProcess based on the universal filter ControlledProcess.

type Converter s ec ic = T ec (SampleRateDep s ic)Source

ecAmp is a set of physical units for the external control parameters, ec is the type for the external control parameters, ic for internal control parameters.

newtype RateDep s ic Source

Constructors

RateDep 

Fields

unRateDep :: ic
 

Instances

C a ic => C a (RateDep s ic) 
Storable ic => Storable (RateDep s ic) 

type Signal s ecAmp ec = T (Phantom s) ecAmp (T ec)Source

makeConverter :: (Amplitude ec -> Displacement ec -> ic) -> Converter s ec icSource

This function is intended for implementing high-level dimensional processors from low-level processors. It introduces the sample rate tag s.

joinSynchronousPlain :: T (Converter s ec ic) (T s (sampleIn, SampleRateDep s ic) sampleOut) -> T s (ec, sampleIn) sampleOutSource

joinSynchronous :: T s u t (T (Converter s ec ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T s u t (T s (ec, sampleIn) sampleOut)Source

joinFirstSynchronousPlain :: T (Converter s ec ic, a) (T s (sampleIn, SampleRateDep s ic) sampleOut) -> T a (T s (ec, sampleIn) sampleOut)Source

joinFirstSynchronous :: T s u t (T (Converter s ec ic, a) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T s u t (T a (T s (ec, sampleIn) sampleOut))Source

runSynchronous1 :: C ecAmp => T s u t (T (Converter s (T ecAmp ec) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T s u t (Signal s ecAmp ec -> T s sampleIn sampleOut)Source

runSynchronousPlain2 :: (C ecAmp0, C ecAmp1) => T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut) -> Signal s ecAmp0 ec0 -> Signal s ecAmp1 ec1 -> T s sampleIn sampleOutSource

runSynchronous2 :: (C ecAmp0, C ecAmp1) => T s u t (T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T s u t (Signal s ecAmp0 ec0 -> Signal s ecAmp1 ec1 -> T s sampleIn sampleOut)Source

runAsynchronous :: (C u, C t) => T t (RateDep s ic) -> T s u t (T (Converter s ec ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T (Dimensional u t) Abstract (T (RateDep s ic)) -> T s u t (T s sampleIn sampleOut)Source

runAsynchronousBuffered :: (C u, C t) => T t (RateDep s ic) -> T s u t (T (Converter s ec ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> T (Dimensional u t) Abstract (T (RateDep s ic)) -> T s u t (T s sampleIn sampleOut)Source

applyConverter1 :: C ecAmp => Converter s (T ecAmp ec) ic -> T (Dimensional u t) ecAmp (T ec) -> T (Dimensional u t) Abstract (T (RateDep s ic))Source

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

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

applyConverter2 :: (C ecAmp0, C ecAmp1) => (T (Recip u) t -> T (Recip u) t -> T (Recip u) t) -> Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic -> T (Dimensional u t) ecAmp0 (T ec0) -> T (Dimensional u t) ecAmp1 (T ec1) -> T (Dimensional u t) Abstract (T (RateDep s ic))Source

runAsynchronous2 :: (C u, C ecAmp0, C ecAmp1, C t) => T t (RateDep s ic) -> T s u t (T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> 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 u, C ecAmp0, C ecAmp1, C t) => T t (RateDep s ic) -> T s u t (T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> 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.

processAsynchronousNaive2 :: (C u, C ecAmp0, C ecAmp1, C t) => T t (RateDep s ic) -> T s u t (T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> 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

processAsynchronousBuffered2 :: (C u, C ecAmp0, C ecAmp1, C t) => T t (RateDep s ic) -> T s u t (T (Converter s (T ecAmp0 ec0, T ecAmp1 ec1) ic) (T s (sampleIn, SampleRateDep s ic) sampleOut)) -> 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.