synthesizer-0.2.0.1: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.Filter.Graph
Synopsis
newtype T filter i t a v = C (Map i [(i, filter t a v)])
newtype Signal list i v = Signal (Map i (list v))
fromList :: Ord i => [(i, [(i, filter t a v)])] -> T filter i t a v
toList :: T filter i t a v -> [(i, [(i, filter t a v)])]
signalFromList :: Ord i => [(i, list v)] -> Signal list i v
signalToList :: Signal list i v -> [(i, list v)]
lookupSignal :: Ord i => Signal list i v -> i -> Maybe (list v)
apply :: (Ord i, Show i, C t, C t, C t, C a v, C a (list v), Filter list filter) => T filter i t a v -> Signal list i v -> Signal list i v
transferFunction :: (Ord i, Show i, C t, Fractional (T t), Scalar (T t), C a t, Filter list filter) => T filter i t a v -> t -> [[T t]]
Documentation
newtype T filter i t a v Source

A filter network is a graph consisting of nodes (input and output signals) and edges (filter processes). Output signals can be taken from every node, inputs can be injected in some nodes which means that the signal at this node is superposed with the injected signal. The same can be achieved by duplicating the network, one duplicate per input, and superposing the corresponding outputs. It is also sensible to setup a graph without inputs, e.g. a recursive filter with some initial conditions that works independent from any input.

In opposition to electric filter networks digital filter networks must be directed.

Test-case: leap-frog filters like

     +-----------[d]-----------+
     v                         |
(u) -+-> [a] (v) -+-> [b] (w) -+-> [c] (y) -+->
                  ^                         |
                  +-----------[e]-----------+
v = a(u + dw)
w = b(v + ey)
y = c w

We model the general network by a list of nodes, where each node is an adder that holds a list of its inputs. Each input of a node is an output of another node that has gone through a processor. Additionally there may be one input from outside. In principle a processor could be a simple filter network as defined by the structure Filter.

The network is an applyable filter whenever each circle contains a delay. To compute the transfer function we have to solve a system of linear equations which we can construct quite straight forward from the processors' input lists.

The current design can be abstractly seen as the system of linear equations:

y = A*y + u

where A is a matrix containing the edges hosting the filters, y the vector of output signals, u the vector of input signals. In this formulation the number of inputs and outputs must match but since you are free to ignore some of the inputs and outputs you can use nodes for pure output, pure input or both of them.

Constructors
C (Map i [(i, filter t a v)])
newtype Signal list i v Source
Constructors
Signal (Map i (list v))
show/hide Instances
(Ord i, Eq a, C a, C (list v), Eq (list v), C a v, C a (list v)) => C a (Signal list i v)
(Ord i, C (list v), Eq (list v)) => C (Signal list i v)
fromList :: Ord i => [(i, [(i, filter t a v)])] -> T filter i t a vSource
toList :: T filter i t a v -> [(i, [(i, filter t a v)])]Source
signalFromList :: Ord i => [(i, list v)] -> Signal list i vSource
signalToList :: Signal list i v -> [(i, list v)]Source
lookupSignal :: Ord i => Signal list i v -> i -> Maybe (list v)Source
apply :: (Ord i, Show i, C t, C t, C t, C a v, C a (list v), Filter list filter) => T filter i t a v -> Signal list i v -> Signal list i vSource
transferFunction :: (Ord i, Show i, C t, Fractional (T t), Scalar (T t), C a t, Filter list filter) => T filter i t a v -> t -> [[T t]]Source

Compute a matrix that tells how an input frequency is mapped to the various output nodes.

According to the formulation given above we have to invert the matrix (I-A).

Currently this is done by a QR decomposition for each frequency. It would be probably faster if we decompose the matrix containing polynomial elements. Then the inverted matrix would consist of some polynomial ratios which can be evaluated for each frequency.

Produced by Haddock version 2.4.2