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

Safe HaskellNone

Synthesizer.Dimensional.Arrow

Contents

Description

A wrapper around (->) or Causal.Process that adds amplitude handling to the Arrow paradigm. This wrapper unifies Synthesizer.Dimensional.Map and Synthesizer.Dimensional.Causal.Process.

Synopsis

Documentation

newtype T arrow sample0 sample1 Source

The sample type parameters can be arbitrarily nested tuples of Samples. Type functions are used for untangling amplitudes and displacements. We use this approach in order to be able to match (as good as possible) the Arrow type class.

Constructors

Cons (Amplitude sample0 -> (arrow (Displacement sample0) (Displacement sample1), Amplitude sample1)) 

Instances

Arrow arrow => Arrow (T arrow)

This instance lacks an implementation for arr. However the syntactic sugar for arrows uses arr for shuffling the operands. Actually shuffling is possible for our arrow, but lifting general functions is a problem. If you want to use arrow syntax, you should hide the arr from Control.Arrow and use the one provided as plain function, here.

Category arrow => Category (T arrow) 

type Single arrow amp0 amp1 yv0 yv1 = T arrow (T amp0 yv0) (T amp1 yv1)Source

class C arrow => Applicable arrow rate Source

Instances

Applicable (->) rate 
Applicable (Core s) (Phantom s) 

apply :: (Transform sig (Displacement sample0), Transform sig (Displacement sample1), Applicable arrow rate) => T arrow sample0 sample1 -> T rate (Amplitude sample0) (sig (Displacement sample0)) -> T rate (Amplitude sample1) (sig (Displacement sample1))Source

applyFlat :: (C yv0 amp0, Transform sig yv0, Transform sig yv1, Applicable arrow rate) => Single arrow (Flat yv0) amp1 yv0 yv1 -> T rate amp0 (sig yv0) -> T rate amp1 (sig yv1)Source

canonicalizeFlat :: (C y flat, Arrow arrow) => Single arrow flat (Flat y) y ySource

applyConst :: (C amp1, C y0, C arrow) => Single arrow (Numeric amp0) amp1 y0 yv1 -> amp0 -> T (Phantom s) amp1 (T yv1)Source

($/:) :: (Applicative f, Transform sig yv0, Transform sig yv1, Applicable arrow rate) => f (Single arrow amp0 amp1 yv0 yv1) -> f (T rate amp0 (sig yv0)) -> f (T rate amp1 (sig yv1))Source

($/-) :: (C amp1, Functor f, C y0, C arrow) => f (Single arrow (Numeric amp0) amp1 y0 yv1) -> amp0 -> f (T (Phantom s) amp1 (T yv1))Source

id :: Category arrow => T arrow sample sampleSource

compose :: Category arrow => T arrow sample0 sample1 -> T arrow sample1 sample2 -> T arrow sample0 sample2Source

arr :: (Arrow arrow, Build sample0, Inspect sample1) => (sample0 -> sample1) -> T arrow sample0 sample1Source

This implementation would work for all fs where the output amplitude does not depend on the input displacement. This is true for all shuffling operations that are needed in the translation of the arrow syntax. However, for the implementation we would need type constraints of the function passed to arr and this is not allowed.

first :: Arrow arrow => T arrow sample0 sample1 -> T arrow (sample0, sample) (sample1, sample)Source

second :: Arrow arrow => T arrow sample0 sample1 -> T arrow (sample, sample0) (sample, sample1)Source

split :: Arrow arrow => T arrow sample0 sample1 -> T arrow sample2 sample3 -> T arrow (sample0, sample2) (sample1, sample3)Source

fanout :: Arrow arrow => T arrow sample sample0 -> T arrow sample sample1 -> T arrow sample (sample0, sample1)Source

map functions

independentMap :: Arrow arrow => (Amplitude sample0 -> Amplitude sample1) -> (Displacement sample0 -> Displacement sample1) -> T arrow sample0 sample1Source

double :: Arrow arrow => T arrow sample (sample, sample)Source

forceDimensionalAmplitude :: (C v, C y, C y yv, Arrow arrow) => T v y -> Single arrow (Dimensional v y) (Dimensional v y) yv yvSource

loop :: ArrowLoop arrow => T arrow (restSampleIn, sample) (restSampleOut, sample) -> T arrow restSampleIn restSampleOutSource

I will call the connection from input to output amplitudes of type amp the looping channel. It is essential, that the looping channel decouples output from input amplitude. You can achieve this by inserting one of the forceAmplitude functions somewhere in the looping channel.

loopVolume :: (C y, C y yv, C v, ArrowLoop arrow) => T v y -> T arrow (restSampleIn, T (Dimensional v y) yv) (restSampleOut, T (Dimensional v y) yv) -> T arrow restSampleIn restSampleOutSource

loop2Volume :: (C y0, C y0 yv0, C v0, C y1, C y1 yv1, C v1, ArrowLoop arrow) => (T v0 y0, T v1 y1) -> T arrow (restSampleIn, (T (Dimensional v0 y0) yv0, T (Dimensional v1 y1) yv1)) (restSampleOut, (T (Dimensional v0 y0) yv0, T (Dimensional v1 y1) yv1)) -> T arrow restSampleIn restSampleOutSource