module Synthesizer.State.Oscillator where
import qualified Synthesizer.Causal.Oscillator as Osci
import qualified Synthesizer.Causal.Oscillator.Core as OsciCore
import qualified Synthesizer.Causal.Process as Causal
import qualified Synthesizer.Basic.WaveSmoothed as WaveSmooth
import qualified Synthesizer.Basic.Wave as Wave
import qualified Synthesizer.Basic.Phase as Phase
import qualified Synthesizer.State.Signal as Sig
import qualified Synthesizer.Generic.Signal as SigG
import qualified Synthesizer.Interpolation as Interpolation
import qualified Algebra.Transcendental as Trans
import qualified Algebra.RealField as RealField
import qualified Algebra.RealRing as RealRing
import NumericPrelude.Numeric (Float, Double, )
static :: (RealRing.C a) => Wave.T a b -> (Phase.T a -> a -> Sig.T b)
static wave phase freq =
Sig.map (Wave.apply wave) (OsciCore.static phase freq)
staticAntiAlias :: (RealRing.C a) =>
WaveSmooth.T a b -> (Phase.T a -> a -> Sig.T b)
staticAntiAlias wave phase freq =
Sig.map (WaveSmooth.apply wave freq) (OsciCore.static phase freq)
phaseMod :: (RealRing.C a) => Wave.T a b -> a -> Sig.T a -> Sig.T b
phaseMod wave freq =
Causal.apply (Osci.phaseMod wave freq)
shapeMod :: (RealRing.C a) =>
(c -> Wave.T a b) -> Phase.T a -> a -> Sig.T c -> Sig.T b
shapeMod wave phase freq =
Causal.apply (Osci.shapeMod wave phase freq)
freqMod :: (RealRing.C a) => Wave.T a b -> Phase.T a -> Sig.T a -> Sig.T b
freqMod wave phase =
Causal.apply (Osci.freqMod wave phase)
freqModAntiAlias :: (RealRing.C a) =>
WaveSmooth.T a b -> Phase.T a -> Sig.T a -> Sig.T b
freqModAntiAlias wave phase =
Causal.apply (Osci.freqModAntiAlias wave phase)
phaseFreqMod :: (RealRing.C a) =>
Wave.T a b -> Sig.T a -> Sig.T a -> Sig.T b
phaseFreqMod wave =
Causal.apply2 (Osci.phaseFreqMod wave)
shapeFreqMod :: (RealRing.C a) =>
(c -> Wave.T a b) -> Phase.T a -> Sig.T c -> Sig.T a -> Sig.T b
shapeFreqMod wave phase =
Causal.apply2 (Osci.shapeFreqMod wave phase)
staticSample :: RealRing.C a =>
Interpolation.T a b -> Sig.T b -> Phase.T a -> a -> Sig.T b
staticSample ip wave phase freq =
Causal.apply (Osci.freqModSample ip wave phase) (Sig.repeat freq)
freqModSample :: RealRing.C a =>
Interpolation.T a b -> Sig.T b -> Phase.T a -> Sig.T a -> Sig.T b
freqModSample ip wave phase =
Causal.apply (Osci.freqModSample ip wave phase)
shapeFreqModSample :: (RealRing.C c, RealRing.C a) =>
Interpolation.T c (Wave.T a b) -> Sig.T (Wave.T a b) ->
c -> Phase.T a ->
Sig.T c -> Sig.T a -> Sig.T b
shapeFreqModSample ip waves shape0 phase =
Causal.apply2 (Osci.shapeFreqModSample ip waves shape0 phase)
shapeFreqModFromSampledTone ::
(RealField.C a, SigG.Transform sig b) =>
Interpolation.T a b ->
Interpolation.T a b ->
a -> sig b ->
a -> Phase.T a ->
Sig.T a -> Sig.T a -> Sig.T b
shapeFreqModFromSampledTone
ipLeap ipStep period sampledTone shape0 phase =
Causal.apply2
(Osci.shapeFreqModFromSampledTone
ipLeap ipStep period sampledTone shape0 phase)
shapePhaseFreqModFromSampledTone ::
(RealField.C a, SigG.Transform sig b) =>
Interpolation.T a b ->
Interpolation.T a b ->
a -> sig b ->
a -> Phase.T a ->
Sig.T a -> Sig.T a -> Sig.T a -> Sig.T b
shapePhaseFreqModFromSampledTone
ipLeap ipStep period sampledTone shape0 phase =
Causal.apply3
(Osci.shapePhaseFreqModFromSampledTone
ipLeap ipStep period sampledTone shape0 phase)
staticSine :: (Trans.C a, RealRing.C a) => Phase.T a -> a -> Sig.T a
staticSine = static Wave.sine
freqModSine :: (Trans.C a, RealRing.C a) => Phase.T a -> Sig.T a -> Sig.T a
freqModSine = freqMod Wave.sine
phaseModSine :: (Trans.C a, RealRing.C a) => a -> Sig.T a -> Sig.T a
phaseModSine = phaseMod Wave.sine
staticSaw :: RealRing.C a => Phase.T a -> a -> Sig.T a
staticSaw = static Wave.saw
freqModSaw :: RealRing.C a => Phase.T a -> Sig.T a -> Sig.T a
freqModSaw = freqMod Wave.saw