synthesizer-llvm-1.0: Efficient signal processing using runtime compilation
Safe HaskellSafe-Inferred
LanguageHaskell98

Synthesizer.LLVM.Server.Packed.Instrument

Synopsis

Documentation

data family InputArg signal a Source #

Instances

Instances details
(Input signal b, a ~ b) => ArgTuple a (InputArg signal b) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

Associated Types

type ArgPlain (InputArg signal b) Source #

Methods

evalTuple :: SampleRate a -> ArgPlain (InputArg signal b) -> InputArg signal b Source #

(a ~ b, Input signal b, Wrapped a f) => Wrapped a (InputArg signal b -> f) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

Associated Types

type Unwrapped (InputArg signal b -> f) Source #

Methods

wrapped :: (InputArg signal b -> f) -> SampleRate a -> Unwrapped (InputArg signal b -> f) Source #

data InputArg (Control b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

data InputArg (Control b) a = Control (T b)
data InputArg (Parameter b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

data InputArg (Signal b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

data InputArg (Signal b) a = Signal (T b)
data InputArg (DetuneModulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

data InputArg (DetuneModulation b) a = DetuneModulation (T (T (T b)), T (T (T (T b))))
data InputArg (FrequencyControl b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

data InputArg (Modulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

data InputArg (Modulation b) a = Modulation (T (T (T (T b))))
type ArgPlain (InputArg signal b) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

type ArgPlain (InputArg signal b) = InputSource signal b
type Unwrapped (InputArg signal b -> f) Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Common

type Unwrapped (InputArg signal b -> f) = InputSource signal b -> Unwrapped f

data Modulation a Source #

Instances

Instances details
(a ~ Exp b, Field b, RationalConstant b) => Input (Modulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

Associated Types

data InputArg (Modulation b) a Source #

type InputSource (Modulation b) a Source #

data InputArg (Modulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

data InputArg (Modulation b) a = Modulation (T (T (T (T b))))
type InputSource (Modulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

type InputSource (Modulation b) a = (T (T (T (T b))), Exp b)

data DetuneModulation a Source #

Instances

Instances details
(a ~ Exp b, Field b, RationalConstant b) => Input (DetuneModulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

Associated Types

data InputArg (DetuneModulation b) a Source #

type InputSource (DetuneModulation b) a Source #

data InputArg (DetuneModulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

data InputArg (DetuneModulation b) a = DetuneModulation (T (T (T b)), T (T (T (T b))))
type InputSource (DetuneModulation b) a Source # 
Instance details

Defined in Synthesizer.LLVM.Server.Packed.Instrument

type InputSource (DetuneModulation b) a = (T (T (T b)), T (T (T (T b))), Exp b)

squareStereoReleaseFM :: IO (Real -> Real -> T Real -> T Real -> T Real -> ChunkSize -> T (T Real) -> Instrument Real (T Vector)) Source #

Square like wave constructed as difference of two phase shifted sawtooth like oscillations.

fenderFM :: IO (Real -> Real -> T Real -> T Real -> T Real -> T Real -> ChunkSize -> T (T Real) -> Instrument Real (T Vector)) Source #

tineBankFM :: IO (Real -> Real -> T Real -> T Real -> T Real -> T Real -> T Real -> T Real -> T Real -> T Real -> T Real -> ChunkSize -> T (T Real) -> Instrument Real (T Vector)) Source #

brass :: IO (Real -> Real -> Real -> Real -> Real -> Real -> T Real -> T Real -> ChunkSize -> T (T Real) -> Instrument Real (T Vector)) Source #

helper functions

for testing

adsr :: IO (Real -> Real -> Real -> Real -> Real -> ChunkSize -> SampleRate Real -> Real -> LazyTime -> T Vector) Source #

The ADSR curve is composed from three parts: Attack, Decay(+Sustain), Release. Attack starts when the key is pressed and lasts attackTime seconds where it reaches height attackPeak*amplitudeOfVelocity. It should be attackPeak>1 because in the following phase we want to approach 1 from above. Say the curve would approach the limit value L if it would continue after the end of the attack phase, the slope is determined by the halfLife with respect to this upper bound. That is, attackHalfLife is the time in seconds where the attack curve reaches or would reach L/2. After Attack the Decay part starts at the same level and decays to amplitudeOfVelocity. The slope is again a halfLife, that is, decayHalfLife is the time where the curve drops from attackPeak*amplitudeOfVelocity to (attackPeak+1)/2*amplitudeOfVelocity. This phase lasts as long as the key is pressed. If the key is released the curve decays with half life releaseHalfLife.