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

Safe HaskellNone

Synthesizer.LLVM.Storable.Signal

Description

Functions on lazy storable vectors that are implemented using LLVM.

Synopsis

Documentation

unpackStrict :: (Storable a, IsPrimitive a, Positive n) => Vector (Plain n a) -> Vector aSource

This function needs only constant time in contrast to unpack.

We cannot provide a pack function since the array size may not line up. It would also need copying since the source data may not be aligned properly.

makeUnpackGenericStrict :: (C vv, n ~ Size vv, va ~ Element vv, C (ReadIt vv), Storable a, MakeValueTuple a, ValueTuple a ~ va, C va, Storable v, MakeValueTuple v, ValueTuple v ~ vv, C vv) => IO (Vector v -> Vector a)Source

This is similar to unpackStrict but performs rearrangement of data. This is for instance necessary for stereo signals where the data layout of packed and unpacked data is different, thus simple casting of the data is not possible. However, for vectorized Stereo data the StereoInterleaved type still uses vector operations for interleaving and thus is more efficient.

makeUnpackGeneric :: (C vv, n ~ Size vv, va ~ Element vv, C (ReadIt vv), Storable a, MakeValueTuple a, ValueTuple a ~ va, C va, Storable v, MakeValueTuple v, ValueTuple v ~ vv, C vv) => IO (Vector v -> Vector a)Source

makeReversePackedStrict :: (Storable v, C vv, n ~ Size vv, va ~ Element vv, MakeValueTuple v, ValueTuple v ~ vv, C vv) => IO (Vector v -> Vector v)Source

makeReversePacked :: (Storable v, C vv, n ~ Size vv, va ~ Element vv, MakeValueTuple v, ValueTuple v ~ vv, C vv) => IO (Vector v -> Vector v)Source

continue :: Storable a => Vector a -> (a -> Vector a) -> Vector aSource

Append two signals where the second signal gets the last value of the first signal as parameter. If the first signal is empty then there is no parameter for the second signal and thus we simply return an empty signal in that case.

continuePacked :: (Positive n, Storable a, IsPrimitive a) => Vector (Plain n a) -> (a -> Vector (Plain n a)) -> Vector (Plain n a)Source

continuePackedGeneric :: (Storable v, Storable a) => (Vector v -> Vector a) -> Vector v -> (a -> Vector v) -> Vector vSource

Use this like

 do unpackGeneric <- makeUnpackGenericStrict
    return (continuePackedGeneric unpackGeneric x y)

fillBuffer :: (MakeValueTuple a, ValueTuple a ~ value, C value) => value -> IO (Word32 -> Ptr a -> IO ())Source

fillBuffer is not only more general than filling with zeros, it also simplifies type inference.

makeMixer :: (Storable a, MakeValueTuple a, ValueTuple a ~ value, C value) => (value -> value -> CodeGenFunction () value) -> IO (Word32 -> Ptr a -> Ptr a -> IO ())Source

addToBuffer :: Storable a => (Word32 -> Ptr a -> Ptr a -> IO ()) -> Int -> Ptr a -> Int -> Vector a -> IO (Int, Vector a)Source

makeArranger :: (Storable a, Additive value, MakeValueTuple a, ValueTuple a ~ value, C value) => IO (ChunkSize -> T Int (Vector a) -> Vector a)Source

arrangeSource

Arguments

:: (Storable a, Additive value, MakeValueTuple a, ValueTuple a ~ value, C value) 
=> ChunkSize 
-> T Int (Vector a)

A list of pairs: (relative start time, signal part), The start time is relative to the start time of the previous event.

-> Vector a

The mixed signal.

Deprecated: better use makeArranger

This is unsafe since it relies on the prior initialization of the LLVM JIT. Better use makeArranger.