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

Safe HaskellNone

Synthesizer.LLVM.Simple.Signal

Synopsis

Documentation

data T a Source

Constructors

forall state ioContext . C state => Cons (forall r c. Phi c => ioContext -> state -> T r c (a, state)) (forall r. ioContext -> CodeGenFunction r state) (IO ioContext) (ioContext -> IO ()) 

Instances

Functor T 
Applicative T

ZipList semantics

(Field a, Real a, RationalConstant a) => Fractional (T a) 
(PseudoRing a, Real a, IntegerConstant a) => Num (T a) 
(Field a, RationalConstant a) => C (T a) 
(PseudoRing a, IntegerConstant a) => C (T a) 
Additive a => C (T a) 

simple :: C state => (forall r c. state -> T r c (a, state)) -> (forall r. CodeGenFunction r state) -> T aSource

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

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

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

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

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

Stretch signal in time by a certain factor.

mix :: Additive a => T a -> T a -> T aSource

envelope :: PseudoRing a => T a -> T a -> T aSource

envelopeStereo :: PseudoRing a => T a -> T (T a) -> T (T a)Source

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

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

iterate :: (FirstClass a, Stored a ~ am, IsSized a, IsSized am, IsConst a) => (forall r. Value a -> CodeGenFunction r (Value a)) -> Value a -> T (Value a)Source

exponential2 :: (C a, IsArithmetic a, FirstClass a, Stored a ~ am, IsSized a, IsSized am, IsConst a) => a -> a -> T (Value a)Source

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

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

osciSaw :: (IntegerConstant a, FirstClass a, Stored a ~ am, IsSized a, IsSized am, Fraction a, IsConst a) => a -> a -> T (Value a)Source

fromStorableVector :: (Storable a, MakeValueTuple a, ValueTuple a ~ value, C value) => Vector a -> T valueSource

fromStorableVectorLazy :: (Storable a, MakeValueTuple a, ValueTuple a ~ value, C value) => Vector a -> T valueSource

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

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

compileChunky :: (C value, Struct value ~ struct, C state, Struct state ~ stateStruct) => (forall r z. Phi z => state -> T r z (value, state)) -> (forall r. CodeGenFunction r state) -> IO (FunPtr (IO (Ptr stateStruct)), FunPtr (Ptr stateStruct -> IO ()), FunPtr (Ptr stateStruct -> Word32 -> Ptr struct -> IO Word32))Source

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

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