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

Synthesizer.LLVM.Parameterized.Signal

Contents

Synopsis

Documentation

data T p a Source

Constructors

forall state packed size ioContext startParamTuple startParamValue startParamPacked startParamSize nextParamTuple nextParamValue nextParamPacked nextParamSize . (Storable startParamTuple, Storable nextParamTuple, MakeValueTuple startParamTuple startParamValue, MakeValueTuple nextParamTuple nextParamValue, Memory startParamValue startParamPacked, Memory nextParamValue nextParamPacked, IsSized startParamPacked startParamSize, IsSized nextParamPacked nextParamSize, Memory state packed, IsSized packed size) => Cons (forall r c. Phi c => nextParamValue -> state -> T r c (a, state)) (forall r. startParamValue -> CodeGenFunction r state) (p -> IO (ioContext, (nextParamTuple, startParamTuple))) (ioContext -> IO ()) 

Instances

Functor (T p) 

simple :: (Storable startParamTuple, Storable nextParamTuple, MakeValueTuple startParamTuple startParamValue, MakeValueTuple nextParamTuple nextParamValue, Memory startParamValue startParamPacked, Memory nextParamValue nextParamPacked, IsSized startParamPacked startParamSize, IsSized nextParamPacked nextParamSize, Memory state packed, IsSized packed size) => (forall r c. Phi c => nextParamValue -> state -> T r c (al, state)) -> (forall r. startParamValue -> CodeGenFunction r state) -> T p nextParamTuple -> T p startParamTuple -> T p alSource

map :: (Storable ph, MakeValueTuple ph pl, Memory pl pp, IsSized pp ps) => (forall r. pl -> a -> CodeGenFunction r b) -> T p ph -> T p a -> T p bSource

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

iterate :: (Storable ph, MakeValueTuple ph pl, Memory pl pp, IsSized pp ps, Storable a, MakeValueTuple a al, Memory al packed, IsSized packed s) => (forall r. pl -> al -> CodeGenFunction r al) -> T p ph -> T p a -> T p alSource

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

mapAccum :: (Storable pnh, MakeValueTuple pnh pnl, Memory pnl pnp, IsSized pnp pns, Storable psh, MakeValueTuple psh psl, Memory psl psp, IsSized psp pss, Memory s struct, IsSized struct sa) => (forall r. pnl -> a -> s -> CodeGenFunction r (b, s)) -> (forall r. psl -> CodeGenFunction r s) -> T p pnh -> T p psh -> T p a -> T p bSource

zipWith :: (Storable ph, MakeValueTuple ph pl, Memory pl pp, IsSized pp ps) => (forall r. pl -> a -> b -> CodeGenFunction r c) -> T p ph -> T p a -> T p b -> T p cSource

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

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

timeline edit

tail :: T p a -> T p aSource

tail empty generates the empty signal.

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

append :: Phi a => T p a -> T p a -> T p aSource

Appending many signals is inefficient, since in cascadingly appended signals the parts are counted in an unary way. Concatenating infinitely many signals is impossible. If you want to concatenate a lot of signals, please render them to lazy storable vectors first.

signal modifiers

interpolateConstant :: (Memory a struct, IsSized struct size, C b, IsFloating b, CmpRet b Bool, Storable b, MakeValueTuple b (Value b), IsConst b, IsFirstClass b, IsSized b sb) => T p b -> T p a -> T p aSource

Stretch signal in time by a certain factor.

This can be used for doing expensive computations of filter parameters at a lower rate. Alternatively, we could provide an adaptive map that recomputes output values only if the input value changes, or if the input value differs from the last processed one by a certain amount.

mix :: IsArithmetic a => T p (Value a) -> T p (Value a) -> T p (Value a)Source

mixStereo :: IsArithmetic a => T p (T (Value a)) -> T p (T (Value a)) -> T p (T (Value a))Source

envelope :: IsArithmetic a => T p (Value a) -> T p (Value a) -> T p (Value a)Source

envelopeStereo :: IsArithmetic a => T p (Value a) -> T p (T (Value a)) -> T p (T (Value a))Source

amplify :: (IsArithmetic a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a size) => T p a -> T p (Value a) -> T p (Value a)Source

amplifyStereo :: (IsArithmetic a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a size) => T p a -> T p (T (Value a)) -> T p (T (Value a))Source

signal generators

constant :: (Storable a, MakeValueTuple a al, Memory al packed, IsSized packed s) => T p a -> T p alSource

exponential2 :: (C a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, IsArithmetic a, IsConst a) => T p a -> T p a -> T p (Value a)Source

exponentialBoundedCore :: (Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, Real a, IsConst a) => T p a -> T p a -> T p a -> T p (Value a)Source

exponentialBounded2 :: (C a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, Real a, IsConst a) => T p a -> T p a -> T p a -> T p (Value a)Source

Exponential curve that remains at the bound value if it would fall below otherwise. This way you can avoid extremal values, e.g. denormalized ones. The initial value and the bound value must be positive.

osciCore :: (Storable t, MakeValueTuple t (Value t), IsFirstClass t, IsSized t size, Fraction t, IsConst t) => T p t -> T p t -> T p (Value t)Source

osci :: (Storable t, MakeValueTuple t (Value t), Storable c, MakeValueTuple c cl, IsFirstClass t, IsSized t size, Memory cl cp, IsSized cp cs, Fraction t, IsConst t) => (forall r. cl -> Value t -> CodeGenFunction r y) -> T p c -> T p t -> T p t -> T p ySource

osciSimple :: (Storable t, MakeValueTuple t (Value t), IsFirstClass t, IsSized t size, Fraction t, IsConst t) => (forall r. Value t -> CodeGenFunction r y) -> T p t -> T p t -> T p ySource

osciSaw :: (C a0, IsConst a0, Replicate a0 a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a size, Fraction a, IsPrimitive a, IsConst a) => T p a -> T p a -> T p (Value a)Source

rampCore :: (Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, IsArithmetic a, IsConst a) => T p a -> T p a -> T p (Value a)Source

parabolaCore :: (Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, IsArithmetic a, IsConst a) => T p a -> T p a -> T p a -> T p (Value a)Source

rampInf :: (C a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, IsArithmetic a, IsConst a) => T p a -> T p (Value a)Source

ramp :: (C a, Storable a, MakeValueTuple a (Value a), IsFirstClass a, IsSized a s, IsArithmetic a, IsConst a) => T p a -> T p (Value a)Source

noise :: (C a, IsFloating a, IsConst a, NumberOfElements D1 a, IsSized a ps, MakeValueTuple a (Value a), Storable a) => T p Word32 -> T p a -> T p (Value a)Source

noise seed rate

The rate parameter is for adjusting the amplitude such that it is uniform across different sample rates and after frequency filters. The rate is the ratio of the current sample rate to the default sample rate, where the variance of the samples would be one. If you want that at sample rate 22050 the variance is 1, then in order to get a consistent volume at sample rate 44100 you have to set rate = 2.

I use the variance as quantity and not the amplitude, because the amplitude makes only sense for uniformly distributed samples. However, frequency filters transform the probabilistic density of the samples towards the normal distribution according to the central limit theorem.

conversion from and to storable vectors

fromStorableVector :: (Storable a, MakeValueTuple a value, Memory value struct) => T p (Vector a) -> T p valueSource

fromStorableVectorLazy :: (Storable a, MakeValueTuple a value, Memory value struct) => T p (Vector a) -> T p valueSource

piecewiseConstant :: (Storable a, MakeValueTuple a value, Memory value struct, IsSized struct size) => T p (T Int a) -> T p valueSource

lazySize :: T p LazySize -> T p ()Source

Turns a lazy chunky size into a signal generator with unit element type. The signal length is the only information that the generator provides. Using zipWith you can use this signal as a lazy take.

derefFillPtr :: Importer (Ptr param -> Word32 -> Ptr a -> IO Word32)Source

run :: (Storable a, MakeValueTuple a value, Memory value struct) => T p value -> IO (Int -> p -> Vector a)Source

render :: (Storable a, MakeValueTuple a value, Memory value struct) => T p value -> Int -> p -> Vector aSource

This is not really a function, see renderChunky.

derefChunkPtr :: Importer (Ptr nextParamStruct -> Ptr stateStruct -> Word32 -> Ptr struct -> IO Word32)Source

compileChunky :: (Memory value struct, Memory state stateStruct, IsSized stateStruct stateSize, Memory startParamValue startParamStruct, Memory nextParamValue nextParamStruct, IsSized startParamStruct startParamSize, IsSized nextParamStruct nextParamSize) => (forall r. nextParamValue -> state -> T r (Value Bool, state) (value, state)) -> (forall r. startParamValue -> CodeGenFunction r state) -> IO (FunPtr (Ptr startParamStruct -> IO (Ptr stateStruct)), FunPtr (Ptr stateStruct -> IO ()), FunPtr (Ptr nextParamStruct -> Ptr stateStruct -> Word32 -> Ptr struct -> IO Word32))Source

runChunkyPattern :: (Storable a, MakeValueTuple a value, Memory value struct) => T p value -> IO (LazySize -> p -> Vector a)Source

Renders a signal generator to a chunky storable vector with given pattern. If the pattern is shorter than the generated signal this means that the signal is shortened.

runChunky :: (Storable a, MakeValueTuple a value, Memory value struct) => T p value -> IO (ChunkSize -> p -> Vector a)Source

renderChunky :: (Storable a, MakeValueTuple a value, Memory value struct) => ChunkSize -> T p value -> p -> Vector aSource

This looks like a function, but it is not a function since it depends on LLVM being initialized with LLVM.initializeNativeTarget before. It is also problematic since you cannot control when and how often the underlying LLVM code is compiled. The compilation cannot be observed, thus it is referential transparent. But this influences performance considerably and I assume that you use this package exclusively for performance reasons.