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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Generator.Signal

Synopsis

Documentation

data T a Source #

Instances
Functor T Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

fmap :: (a -> b) -> T a -> T b #

(<$) :: a -> T b -> T a #

Applicative T Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

pure :: a -> T a #

(<*>) :: T (a -> b) -> T a -> T b #

liftA2 :: (a -> b -> c) -> T a -> T b -> T c #

(*>) :: T a -> T b -> T b #

(<*) :: T a -> T b -> T a #

(Field a, Real a, RationalConstant a) => Fractional (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

(/) :: T a -> T a -> T a #

recip :: T a -> T a #

fromRational :: Rational -> T a #

(PseudoRing a, Real a, IntegerConstant a) => Num (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

(+) :: T a -> T a -> T a #

(-) :: T a -> T a -> T a #

(*) :: T a -> T a -> T a #

negate :: T a -> T a #

abs :: T a -> T a #

signum :: T a -> T a #

fromInteger :: Integer -> T a #

(Phi a, Undefined a) => Semigroup (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

(<>) :: T a -> T a -> T a #

sconcat :: NonEmpty (T a) -> T a #

stimes :: Integral b => b -> T a -> T a #

(Phi a, Undefined a) => Monoid (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

mempty :: T a #

mappend :: T a -> T a -> T a #

mconcat :: [T a] -> T a #

(Field a, RationalConstant a) => C (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

(/) :: T a -> T a -> T a #

recip :: T a -> T a #

fromRational' :: Rational -> T a #

(^-) :: T a -> Integer -> T a #

(PseudoRing a, IntegerConstant a) => C (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

(*) :: T a -> T a -> T a #

one :: T a #

fromInteger :: Integer -> T a #

(^) :: T a -> Integer -> T a #

Additive a => C (T a) Source # 
Instance details

Defined in Synthesizer.LLVM.Generator.Private

Methods

zero :: T a #

(+) :: T a -> T a -> T a #

(-) :: T a -> T a -> T a #

negate :: T a -> T a #

type ProcessOf T Source # 
Instance details

Defined in Synthesizer.LLVM.Causal.Private

type ProcessOf T = T

type MV a = T (T a) Source #

constant :: (Aggregate ae al, C al) => ae -> T al Source #

fromArray :: (Natural n, C a) => ((n :*: SizeOf (Struct a)) ~ arrSize, Natural arrSize) => Exp (Array n a) -> MV a Source #

iterate :: C a => (Exp a -> Exp a) -> Exp a -> MV a Source #

takeWhile :: Aggregate ae a => (ae -> Exp Bool) -> T a -> T a Source #

take :: Exp Word -> T a -> T a Source #

tail :: T a -> T a Source #

tail empty generates the empty signal.

drop :: Exp Word -> T a -> T a Source #

append :: (Phi a, Undefined a) => T a -> T a -> T a Source #

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.

cycle :: (Phi a, Undefined a) => T a -> T a Source #

cycle empty == empty

amplify :: (Aggregate ea a, C a, PseudoRing a) => ea -> T a -> T a Source #

osci :: (Fraction t, C t) => (forall r. T t -> CodeGenFunction r y) -> Exp t -> Exp t -> T y Source #

exponential2 :: C a => Real a => RationalConstant a => Transcendental a => Exp a -> Exp a -> MV a Source #

exponentialBounded2 :: C a => Real a => RationalConstant a => Transcendental a => Exp a -> Exp a -> Exp a -> MV a Source #

noise :: (C a, Transcendental a, RationalConstant a, NativeFloating a ar) => Exp Word32 -> Exp a -> MV 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.

adjacentNodes02 :: C a => T a -> T (Nodes02 a) Source #

adjacentNodes13 :: (C a, T a ~ al) => Exp a -> T al -> T (Nodes13 al) Source #

interpolateConstant :: (C a, C b, IntegerConstant b, Additive b, Comparison b) => Exp b -> T a -> T a Source #

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.

rampSlope :: (C a, Field a, IntegerConstant a) => Exp a -> MV a Source #

rampInf :: (C a, Field a, IntegerConstant a) => Exp a -> MV a Source #

ramp :: (C a, Field a, IntegerConstant a, NativeFloating a ar) => Exp Word -> MV a Source #

parabolaFadeInInf :: (C a, Field a, IntegerConstant a) => Exp a -> MV a Source #

parabolaFadeOutInf :: (C a, Field a, IntegerConstant a) => Exp a -> MV a Source #

parabolaFadeIn :: (C a, Field a, IntegerConstant a, NativeFloating a ar) => Exp Word -> MV a Source #

parabolaFadeOut :: (C a, Field a, IntegerConstant a, NativeFloating a ar) => Exp Word -> MV a Source #

parabolaFadeInMap :: (C a, Field a, IntegerConstant a, NativeFloating a ar) => Exp Word -> MV a Source #

parabolaFadeOutMap :: (C a, Field a, IntegerConstant a, NativeFloating a ar) => Exp Word -> MV a Source #