synthesizer-llvm-0.6: Efficient signal processing using runtime compilation

Safe HaskellNone

Synthesizer.LLVM.CausalParameterized.Process

Synopsis

Documentation

data T p a b Source

Constructors

forall context state ioContext parameters . (Storable parameters, MakeValueTuple parameters, C (ValueTuple parameters), C context, C state) => Cons (forall r c. Phi c => context -> a -> state -> T r c (b, state)) (forall r. ValueTuple parameters -> CodeGenFunction r (context, state)) (forall r. context -> state -> CodeGenFunction r ()) (p -> IO (ioContext, parameters)) (ioContext -> IO ()) 

Instances

Arrow (T p) 
Category (T p) 
C (T p) 
C (T p) 
Functor (T p a) 
Applicative (T p a) 
(Field b, Real b, RationalConstant b) => Fractional (T p a b) 
(PseudoRing b, Real b, IntegerConstant b) => Num (T p a b) 
(Field b, RationalConstant b) => C (T p a b) 
(PseudoRing b, IntegerConstant b) => C (T p a b) 
Additive b => C (T p a b) 

simple :: (Storable parameters, MakeValueTuple parameters, ValueTuple parameters ~ paramValue, C paramValue, C context, C state) => (forall r c. Phi c => context -> a -> state -> T r c (b, state)) -> (forall r. paramValue -> CodeGenFunction r (context, state)) -> T p parameters -> T p a bSource

fromSignal :: T p b -> T p a bSource

toSignal :: T p () a -> T p aSource

mapAccum :: (Storable pnh, MakeValueTuple pnh, ValueTuple pnh ~ pnl, C pnl, Storable psh, MakeValueTuple psh, ValueTuple psh ~ psl, C psl, C s) => (forall r. pnl -> a -> s -> CodeGenFunction r (b, s)) -> (forall r. psl -> CodeGenFunction r s) -> T p pnh -> T p psh -> T p a bSource

map :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, C pl) => (forall r. pl -> a -> CodeGenFunction r b) -> T p ph -> T p a bSource

mapSimple :: (forall r. a -> CodeGenFunction r b) -> T p a bSource

zipWith :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, C pl) => (forall r. pl -> a -> b -> CodeGenFunction r c) -> T p ph -> T p (a, b) cSource

zipWithSimple :: (forall r. a -> b -> CodeGenFunction r c) -> T p (a, b) cSource

apply :: T p a b -> T p a -> T p bSource

compose :: T p a b -> T p b c -> T p a cSource

first :: T p b c -> T p (b, d) (c, d)Source

feedFst :: T p a -> T p b (a, b)Source

feedSnd :: T p a -> T p b (b, a)Source

loop :: (Storable c, MakeValueTuple c, ValueTuple c ~ cl, C cl) => T p c -> T p (a, cl) (b, cl) -> T p a bSource

Not quite the loop of ArrowLoop because we need a delay of one time step and thus an initialization value.

For a real ArrowLoop.loop, that is a zero-delay loop, we would formally need a MonadFix instance of CodeGenFunction. But this will not become reality, since LLVM is not able to re-order code in a way that allows to access a result before creating the input.

loopZero :: (C process, Additive c, C c) => process (a, c) (b, c) -> process a bSource

take :: T p Int -> T p a aSource

takeWhile :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, C pl) => (forall r. pl -> a -> CodeGenFunction r (Value Bool)) -> T p ph -> T p a aSource

integrate :: (Storable a, Additive al, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p al alSource

The first output value is the initial value. Thus integrate delays by one sample compared with integrateSync.

($<) :: T p (a, b) c -> T p a -> T p b cSource

($>) :: T p (a, b) c -> T p b -> T p a cSource

($*) :: T p a b -> T p a -> T p bSource

($<#) :: (Storable ah, MakeValueTuple ah, ValueTuple ah ~ a, C a) => T p (a, b) c -> ah -> T p b cSource

($>#) :: (Storable bh, MakeValueTuple bh, ValueTuple bh ~ b, C b) => T p (a, b) c -> bh -> T p a cSource

($*#) :: (Storable ah, MakeValueTuple ah, ValueTuple ah ~ a, C a) => T p a b -> ah -> T p bSource

provide constant input in a comfortable way

applyFst :: T p (a, b) c -> T p a -> T p b cSource

applySnd :: T p (a, b) c -> T p b -> T p a cSource

mapAccumSimple :: C s => (forall r. a -> s -> CodeGenFunction r (b, s)) -> (forall r. CodeGenFunction r s) -> T p a bSource

replicateControlled :: (Undefined x, Phi x) => T p Int -> T p (c, x) x -> T p (c, x) xSource

serial replication

But you may also use it for a parallel replication, see replicateParallel.

replicateParallel :: (Undefined b, Phi b) => T p Int -> T p b -> T p (b, b) b -> T p a b -> T p a bSource

replicateControlledParam :: (Undefined x, Phi x) => (forall q. T q p -> T q a -> T q (c, x) x) -> T p [a] -> T p (c, x) xSource

feedbackControlled :: (Storable ch, MakeValueTuple ch, ValueTuple ch ~ c, C c) => T p ch -> T p ((ctrl, a), c) b -> T p (ctrl, b) c -> T p (ctrl, a) bSource

feedbackControlledZero :: (C process, Additive c, C c) => process ((ctrl, a), c) b -> process (ctrl, b) c -> process (ctrl, a) bSource

fromModifier :: C process => (Flatten ah, Registers ah ~ al, Flatten bh, Registers bh ~ bl, Flatten ch, Registers ch ~ cl, Flatten sh, Registers sh ~ sl, C sl) => Simple sh ch ah bh -> process (cl, al) blSource

stereoFromMono :: (Phi a, Phi b, Undefined b) => T p a b -> T p (T a) (T b)Source

Run a causal process independently on each stereo channel.

stereoFromMonoControlled :: (Phi a, Phi b, Phi c, Undefined b) => T p (c, a) b -> T p (c, T a) (T b)Source

stereoFromMonoParameterized :: (Phi a, Phi b, Undefined b) => (forall q. T q p -> T q x -> T q a b) -> T p (T x) -> T p (T a) (T b)Source

stereoFromVector :: (C process, IsPrimitive a, IsPrimitive b) => process (Value (Vector D2 a)) (Value (Vector D2 b)) -> process (T (Value a)) (T (Value b))Source

vectorize :: (C process, C va, n ~ Size va, a ~ Element va, C vb, n ~ Size vb, b ~ Element vb) => process a b -> process va vbSource

replaceChannel :: (C process, C va, n ~ Size va, a ~ Element va, C vb, n ~ Size vb, b ~ Element vb) => Int -> process a b -> process va vb -> process va vbSource

Given a vector process, replace the i-th output by output that is generated by a scalar process from the i-th input.

arrayElement :: (C process, Array dim a ~ array, GetValue array index, IsFirstClass a, ValueType array index ~ a, NaturalT index, NaturalT dim, (index :<: dim) ~ True) => index -> process (Value (Array dim a)) (Value a)Source

Read the i-th element from each array.

element :: (C process, IsFirstClass a, GetValue agg index, ValueType agg index ~ a) => index -> process (Value agg) (Value a)Source

Read the i-th element from an aggregate type.

mix :: Additive a => T p (a, a) aSource

You may also use '(+)'.

raise :: (Additive al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p al alSource

You may also use '(+)' and a constant signal or a number literal.

envelope :: PseudoRing a => T p (a, a) aSource

You may also use '(*)'.

envelopeStereo :: PseudoRing a => T p (a, T a) (T a)Source

amplify :: (PseudoRing al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p al alSource

You may also use '(*)' and a constant signal or a number literal.

amplifyStereo :: (PseudoRing al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p (T al) (T al)Source

mapLinear :: (IsArithmetic a, Storable a, FirstClass a, Stored a ~ am, IsSized a, IsSized am, MakeValueTuple a, ValueTuple a ~ Value a) => T p a -> T p a -> T p (Value a) (Value a)Source

quantizeLift :: (C b, Storable c, MakeValueTuple c, ValueTuple c ~ Value cl, IntegerConstant cl, IsFloating cl, CmpRet cl, CmpResult cl ~ Bool, FirstClass cl, Stored cl ~ cm, IsSized cm) => T p c -> T p a b -> T p a bSource

quantizeLift k f applies the process f to every kth sample and repeats the result k times.

Like interpolateConstant this function can be used for computation of filter parameters at a lower rate. This can be useful, if you have a frequency control signal at sample rate that shall be used both for an oscillator and a frequency filter.

osciSimple :: (FirstClass t, Stored t ~ tm, IsSized t, IsSized tm, Fraction t) => (forall r. Value t -> CodeGenFunction r y) -> T p (Value t, Value t) ySource

osciCore :: (FirstClass t, Stored t ~ tm, IsSized tm, Fraction t) => T p (Value t, Value t) (Value t)Source

Compute the phases from phase distortions and frequencies.

It's like integrate but with wrap-around performed by fraction. For FM synthesis we need also negative phase distortions, thus we use addToPhase which supports that.

osciCoreSync :: (FirstClass t, Stored t ~ tm, IsSized tm, Fraction t) => T p (Value t, Value t) (Value t)Source

Compute the phases from phase distortions and frequencies.

It's like integrate but with wrap-around performed by fraction. For FM synthesis we need also negative phase distortions, thus we use addToPhase which supports that.

shapeModOsci :: (FirstClass t, Stored t ~ tm, IsSized t, IsSized tm, Fraction t) => (forall r. c -> Value t -> CodeGenFunction r y) -> T p (c, (Value t, Value t)) ySource

delay :: (Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p Int -> T p al alSource

Delay time must be non-negative.

The initial value is needed in order to determine the ring buffer element type.

delayZero :: (C a, Additive a) => T p Int -> T p a aSource

delay1 :: (Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p al alSource

Delay by one sample. For very small delay times (say up to 8) it may be more efficient to apply delay1 several times or to use a pipeline, e.g. pipeline (id :: T (Vector D4 Float) (Vector D4 Float)) delays by 4 samples in an efficient way. In principle it would be also possible to use unpack (delay1 (const $ toVector (0,0,0,0))) but unpack causes an additional delay. Thus unpack (id :: T (Vector D4 Float) (Vector D4 Float)) may do, what you want.

delay1Zero :: (C a, Additive a) => T p a aSource

delayControlled :: (Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p Int -> T p (Value Word32, al) alSource

Delay by a variable amount of samples. The momentum delay must be between 0 and maxTime, inclusively.

delayControlledInterpolated :: (C nodes, Storable vh, MakeValueTuple vh, ValueTuple vh ~ v, C v, IsFloating a, NumberOfElements a ~ D1) => (forall r. T r nodes (Value a) v) -> T p vh -> T p Int -> T p (Value a, v) vSource

Delay by a variable fractional amount of samples. Non-integer delays are achieved by linear interpolation. The momentum delay must be between 0 and maxTime, inclusively.

differentiate :: (Additive al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p al alSource

comb :: (PseudoRing al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p Int -> T p al alSource

Delay time must be greater than zero!

combStereo :: (PseudoRing al, Storable a, MakeValueTuple a, ValueTuple a ~ al, C al) => T p a -> T p Int -> T p (T al) (T al)Source

reverb :: (Random a, IsArithmetic a, RationalConstant a, MakeValueTuple a, ValueTuple a ~ Value a, Storable a, FirstClass a, Stored a ~ am, IsSized am, RandomGen g) => g -> Int -> (a, a) -> (Int, Int) -> T p (Value a) (Value a)Source

Example: apply a stereo reverb to a mono sound.

 traverse
    (\seed -> reverb (Random.mkStdGen seed) 16 (0.92,0.98) (200,1000))
    (Stereo.cons 42 23)

reverbEfficient :: (Random a, PseudoModule a, Scalar a ~ s, IsFloating s, IntegerConstant s, NumberOfElements s ~ D1, MakeValueTuple a, ValueTuple a ~ Value a, Storable a, FirstClass a, Stored a ~ am, IsSized am, RandomGen g) => T p g -> T p Int -> T p (a, a) -> T p (Int, Int) -> T p (Value a) (Value a)Source

pipeline :: (C v, a ~ Element v, Zero v, C v) => T p v v -> T p a aSource

This allows to compute a chain of equal processes efficiently, if all of these processes can be bundled in one vectorial process. Applications are an allpass cascade or an FM operator cascade.

The function expects that the vectorial input process works like parallel scalar processes. The different pipeline stages may be controlled by different parameters, but the structure of all pipeline stages must be equal. Our function feeds the input of the pipelined process to the zeroth element of the Vector. The result of processing the i-th element (the i-th channel, so to speak) is fed to the (i+1)-th element. The (n-1)-th element of the vectorial process is emitted as output of pipelined process.

The pipeline necessarily introduces a delay of (n-1) values. For simplification we extend this to n values delay. If you need to combine the resulting signal from the pipeline with another signal in a zip-like way, you may delay that signal with pipeline id. The first input values in later stages of the pipeline are initialized with zero. If this is not appropriate for your application, then we may add a more sensible initialization.

skip :: (Undefined v, Phi v, C v) => T p v -> T p (Value Word32) vSource

Feeds a signal into a causal process while holding or skipping signal elements according to the process input. The skip happens after a value is passed from the fed signal.

skip x $* 0 repeats the first signal value in the output. skip x $* 1 feeds the signal to the output as is. skip x $* 2 feeds the signal to the output with double speed.

frequencyModulation :: (IntegerConstant a, IsFloating a, CmpRet a, CmpResult a ~ Bool, FirstClass a, Stored a ~ am, IsSized am, Undefined nodes, Phi nodes, C nodes) => (forall r. Value a -> nodes -> CodeGenFunction r v) -> T p nodes -> T p (Value a) vSource

frequencyModulationLinear :: (IntegerConstant a, IsFloating a, CmpRet a, CmpResult a ~ Bool, FirstClass a, Stored a ~ am, IsSized am) => T p (Value a) -> T p (Value a) (Value a)Source

 frequencyModulationLinear signal

is a causal process mapping from a shrinking factor to the modulated input signal. Similar to interpolateConstant but the factor is reciprocal and controllable and we use linear interpolation. The shrinking factor must be non-negative.

adjacentNodes02 :: (C a, Undefined a) => T p a -> T p (Nodes02 a)Source

adjacentNodes13 :: (MakeValueTuple ah, Storable ah, ValueTuple ah ~ a, C a, Undefined a) => T p ah -> T p a -> T p (Nodes13 a)Source

trigger :: (Storable a, MakeValueTuple a, ValueTuple a ~ al, Select al, C al) => T p a -> T p al -> T p (Value Bool) alSource

trigger fill signal send signal to the output and restart it whenever the Boolean process input is True. Before the first occurrence of True and between instances of the signal the output is filled with the fill value.

Attention: This function will crash if the input generator uses fromStorableVectorLazy, piecewiseConstant or lazySize, since these functions contain mutable references and in-place updates, and thus they cannot read lazy Haskell data multiple times.

runStorable :: (Storable a, MakeValueTuple a, ValueTuple a ~ valueA, C valueA, Storable b, MakeValueTuple b, ValueTuple b ~ valueB, C valueB) => T p valueA valueB -> IO (p -> Vector a -> Vector b)Source

applyStorable :: (Storable a, MakeValueTuple a, ValueTuple a ~ valueA, C valueA, Storable b, MakeValueTuple b, ValueTuple b ~ valueB, C valueB) => T p valueA valueB -> p -> Vector a -> Vector bSource

runStorableChunky :: (Storable a, MakeValueTuple a, ValueTuple a ~ valueA, C valueA, Storable b, MakeValueTuple b, ValueTuple b ~ valueB, C valueB) => T p valueA valueB -> IO (p -> Vector a -> Vector b)Source

runStorableChunkyCont :: (Storable a, MakeValueTuple a, ValueTuple a ~ valueA, C valueA, Storable b, MakeValueTuple b, ValueTuple b ~ valueB, C valueB) => T p valueA valueB -> IO ((Vector a -> Vector b) -> p -> Vector a -> Vector b)Source

This function should be used instead of StorableVector.Lazy.Pattern.splitAt and subsequent append, because it does not have the risk of a memory leak.

applyStorableChunky :: (Storable a, MakeValueTuple a, ValueTuple a ~ valueA, C valueA, Storable b, MakeValueTuple b, ValueTuple b ~ valueB, C valueB) => T p valueA valueB -> p -> Vector a -> Vector bSource

processIO :: (Read a, Default a, Default d) => T p (Element a) (Element d) -> IO (p -> T a d)Source

processIOCore :: Read a => T a b -> T p b c -> T c d -> IO (p -> T a d)Source