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

Safe HaskellNone

Synthesizer.LLVM.Causal.Process

Synopsis

Documentation

class (C process, C (SignalOf process)) => C process whereSource

Methods

simple :: C state => (forall r c. Phi c => a -> state -> T r c (b, state)) -> (forall r. CodeGenFunction r state) -> process a bSource

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

Instances

C T 
C (T p) 

data T a b Source

Instances

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

amplify :: (C process, IsArithmetic a, IsConst a) => a -> process (Value a) (Value a)Source

amplifyStereo :: (C process, IsArithmetic a, IsConst a) => a -> process (T (Value a)) (T (Value a))Source

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

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

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

applyConst :: (MakeValueTuple a, ValueTuple a ~ al) => T al b -> a -> T bSource

applyConstFst :: (MakeValueTuple a, ValueTuple a ~ al) => T (al, b) c -> a -> T b cSource

applyConstSnd :: (MakeValueTuple b, ValueTuple b ~ bl) => T (a, bl) c -> b -> T a cSource

($<) :: C process => process (a, b) c -> SignalOf process a -> process b c

($>) :: C process => process (a, b) c -> SignalOf process b -> process a c

($*) :: C process => process a b -> SignalOf process a -> SignalOf process b

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

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

($*#) :: (C process, SignalOf process ~ signal, Storable ah, MakeValueTuple ah, ValueTuple ah ~ a, C a) => process a b -> ah -> signal bSource

provide constant input in a comfortable way

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

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

feedConstFst :: (MakeValueTuple a, ValueTuple a ~ al) => a -> T b (al, b)Source

feedConstSnd :: (MakeValueTuple a, ValueTuple a ~ al) => a -> T b (b, al)Source

first :: C process => process b c -> process (b, d) (c, d)Source

envelope :: (C process, PseudoRing a) => process (a, a) aSource

You may also use '(*)'.

envelopeStereo :: (C process, PseudoRing a) => process (a, T a) (T a)Source

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

fromSignal :: T b -> T a bSource

toSignal :: T () a -> T aSource

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

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

Like loop but uses zero as initial value and it does not need a zero as Haskell value.

delay1Zero :: (C process, Additive a, C a) => process a aSource

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

map :: C process => (forall r. a -> CodeGenFunction r b) -> process a bSource

mapAccum :: (C process, C state) => (forall r. a -> state -> CodeGenFunction r (b, state)) -> (forall r. CodeGenFunction r state) -> process a bSource

zipWith :: C process => (forall r. a -> b -> CodeGenFunction r c) -> process (a, b) cSource

mapProc :: C process => (forall r. b -> CodeGenFunction r c) -> process a b -> process a cSource

zipProcWith :: C process => (forall r. b -> c -> CodeGenFunction r d) -> process a b -> process a c -> process a dSource

mix :: (C process, Additive a) => process (a, a) aSource

You may also use '(+)'.

pipeline :: (C process, Positive n, C x, v ~ T n x, a ~ T x, Zero v, C v) => process v v -> process 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 the 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.

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, Positive n, C x, T x ~ a, T n x ~ va, C y, T y ~ b, T n y ~ vb) => process a b -> process va vbSource

replaceChannel :: (C process, Positive n, C x, T x ~ a, T n x ~ va, C y, T y ~ b, T n y ~ 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, IsFirstClass a, Natural index, Natural dim, index :<: dim) => Proxy 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.

osciCoreSync :: (C process, C t, Fraction t) => process (t, t) tSource

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.

osciCore :: (C process, C t, Fraction t) => process (t, t) tSource

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.

osci :: (C process, C t, Fraction t) => (forall r. t -> CodeGenFunction r y) -> process (t, t) ySource

shapeModOsci :: (C process, C t, Fraction t) => (forall r. c -> t -> CodeGenFunction r y) -> process (c, (t, t)) ySource

skip :: (C process, SignalOf process ~ signal, Undefined a, Phi a, C a) => signal a -> process (Value Word32) aSource

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.

foldChunks :: (C process, SignalOf process ~ signal, Undefined b, Phi b) => T a b -> signal a -> process (Value Word32) bSource

The input of the process is a sequence of chunk sizes. The signal is chopped into chunks of these sizes and each chunk is folded using the given initial value and the accumulation function. A trailing incomplete chunk will be ignored.

foldChunksPartial :: (C process, SignalOf process ~ signal, Undefined a, Phi a, Undefined b, Phi b) => T a b -> signal a -> process (Value Word32) bSource

Like foldChunks but an incomplete chunk at the end is treated like a complete one.

frequencyModulation :: (C process, SignalOf process ~ signal, 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) -> signal nodes -> process (Value a) vSource

interpolateConstant :: (C process, SignalOf process ~ signal, C a, FirstClass b, Stored b ~ bm, IsSized bm, IntegerConstant b, IsFloating b, CmpRet b, CmpResult b ~ Bool) => signal a -> process (Value b) aSource

Stretch signal in time by a time-varying factor.

quantizeLift :: (C process, C b, IntegerConstant c, IsFloating c, CmpRet c, CmpResult c ~ Bool, FirstClass c, Stored c ~ cm, IsSized cm) => process a b -> process (Value c, a) bSource

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

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

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