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

Synthesizer.LLVM.Causal.Process

Synopsis

Documentation

data T a b Source

Constructors

forall state packed size ioContext . (Memory state packed, IsSized packed size) => Cons (forall r c. Phi c => ioContext -> a -> state -> T r c (b, state)) (forall r. ioContext -> CodeGenFunction r state) (IO ioContext) (ioContext -> IO ()) 

Instances

simple :: (Memory state packed, IsSized packed size) => (forall r c. Phi c => a -> state -> T r c (b, state)) -> (forall r. CodeGenFunction r state) -> T a bSource

toSignal :: T () a -> T aSource

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

mapAccum :: (Memory state packed, IsSized packed size) => (forall r. a -> state -> CodeGenFunction r (b, state)) -> (forall r. CodeGenFunction r state) -> T a bSource

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

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

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

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

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

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

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

mixStereo :: IsArithmetic a => T (T (Value a), T (Value a)) (T (Value a))Source

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

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

applyStorable :: (Storable a, MakeValueTuple a valueA, Memory valueA structA, Storable b, MakeValueTuple b valueB, Memory valueB structB) => T valueA valueB -> Vector a -> Vector bSource

derefStartPtr :: Importer (IO (Ptr stateStruct))Source

derefStopPtr :: Importer (Ptr stateStruct -> IO ())Source

derefChunkPtr :: Importer (Ptr stateStruct -> Word32 -> Ptr aStruct -> Ptr bStruct -> IO Word32)Source

compileChunky :: (Memory aValue aStruct, Memory bValue bStruct, Memory state stateStruct, IsSized stateStruct stateSize) => (forall r. aValue -> state -> T r (Value Bool, (Value (Ptr bStruct), state)) (bValue, state)) -> (forall r. CodeGenFunction r state) -> IO (FunPtr (IO (Ptr stateStruct)), FunPtr (Ptr stateStruct -> IO ()), FunPtr (Ptr stateStruct -> Word32 -> Ptr aStruct -> Ptr bStruct -> IO Word32))Source

runStorableChunky :: (Storable a, MakeValueTuple a valueA, Memory valueA structA, Storable b, MakeValueTuple b valueB, Memory valueB structB) => T valueA valueB -> IO (Vector a -> Vector b)Source

This function will not work as expected, since feeding a lazy storable vector to the causal process means that createIOContext creates a StablePtr to an IORef refering to a chunk list. The IORef will be created once for all uses of the generated function of type (SVL.Vector a -> SVL.Vector b). This means that the pointer into the chunks list will conflict. An alternative would be to create the StablePtr in a foreign function that calls back to Haskell. But this way is disallowed for foreign finalizers.

applyStorableChunky :: (Storable a, MakeValueTuple a valueA, Memory valueA structA, Storable b, MakeValueTuple b valueB, Memory valueB structB) => T valueA valueB -> Vector a -> Vector bSource