{-# OPTIONS -fno-implicit-prelude #-} {- | Copyright : (c) Henning Thielemann 2006 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes Tone generators Frequencies are always specified in ratios of the sample rate, e.g. the frequency 0.01 for the sample rate 44100 Hz means a physical frequency of 441 Hz. -} module Synthesizer.Generic.Oscillator where -- import qualified Synthesizer.Plain.ToneModulation as ToneMod import qualified Synthesizer.Basic.Wave as Wave import qualified Synthesizer.Basic.Phase as Phase import qualified Synthesizer.Generic.Interpolation as Interpolation import qualified Synthesizer.Generic.Signal as SigG import qualified Synthesizer.Generic.SampledValue as Sample {- import qualified Algebra.RealTranscendental as RealTrans import qualified Algebra.Module as Module import qualified Algebra.VectorSpace as VectorSpace import Algebra.Module((*>)) -} import qualified Algebra.Transcendental as Trans import qualified Algebra.RealField as RealField -- import qualified Algebra.Field as Field import qualified Algebra.Ring as Ring import qualified Algebra.Additive as Additive -- import qualified Number.NonNegative as NonNeg import NumericPrelude -- import qualified Prelude as P import PreludeBase {- * Oscillators with arbitrary but constant waveforms -} freqToPhase :: (RealField.C a, Sample.C a, SigG.C sig) => Phase.T a -> sig a -> sig (Phase.T a) freqToPhase phase freq = SigG.scanL (flip Phase.increment) phase freq {- | oscillator with constant frequency -} static :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Wave.T a b -> (Phase.T a -> a -> sig b) static wave phase freq = SigG.map (Wave.apply wave) (SigG.iterate (Phase.increment freq) phase) {- | oscillator with modulated frequency -} freqMod :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Wave.T a b -> Phase.T a -> sig a -> sig b freqMod wave phase freqs = SigG.map (Wave.apply wave) (freqToPhase phase freqs) {- | oscillator with modulated phase -} phaseMod :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Wave.T a b -> a -> sig a -> sig b phaseMod wave = shapeMod (Wave.phaseOffset wave) zero {- | oscillator with modulated shape -} shapeMod :: (RealField.C a, Sample.C a, Sample.C b, Sample.C c, SigG.C sig) => (c -> Wave.T a b) -> Phase.T a -> a -> sig c -> sig b shapeMod wave phase freq parameters = SigG.zipWith (Wave.apply . wave) parameters (SigG.iterate (Phase.increment freq) phase) {- | oscillator with both phase and frequency modulation -} phaseFreqMod :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Wave.T a b -> sig a -> sig a -> sig b phaseFreqMod wave = shapeFreqMod (Wave.phaseOffset wave) zero {- | oscillator with both shape and frequency modulation -} shapeFreqMod :: (RealField.C a, Sample.C a, Sample.C b, Sample.C c, SigG.C sig) => (c -> Wave.T a b) -> Phase.T a -> sig c -> sig a -> sig b shapeFreqMod wave phase parameters freqs = SigG.zipWith (Wave.apply . wave) parameters (freqToPhase phase freqs) {- | oscillator with a sampled waveform with constant frequency This is essentially an interpolation with cyclic padding. -} staticSample :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Interpolation.T sig a b -> [b] -> Phase.T a -> a -> sig b staticSample ip wave phase freq = freqModSample ip wave phase (SigG.repeat freq) {- | oscillator with a sampled waveform with modulated frequency Should behave homogenously for different types of interpolation. -} freqModSample :: (RealField.C a, Sample.C a, Sample.C b, SigG.C sig) => Interpolation.T sig a b -> [b] -> Phase.T a -> sig a -> sig b freqModSample ip wave phase freqs = let len = length wave in Interpolation.multiRelativeCyclicPad ip (Phase.toRepresentative $ Phase.multiply len phase) (SigG.map (* fromIntegral len) freqs) (SigG.fromList wave) {- {- | Shape control is a list of relative changes, each of which must be non-negative in order to allow lazy processing. '1' advances by one wave. Frequency control can be negative. If you want to use sampled waveforms as well then use 'Wave.sample' in the list of waveforms. With sampled waves this function is identical to HunkTranspose in Assampler. Example: interpolate different versions of 'Wave.oddCosine' and 'Wave.oddTriangle'. You could also chop a tone into single waves and use the waves as input for this function but you certainly want to use 'Wave.sampledTone' or 'shapeFreqModFromSampledTone' instead, because in the wave information for 'shapeFreqModSample' shape and phase are strictly separated. -} shapeFreqModSample :: (RealField.C c, RealField.C b, Sample.C a, SigG.C sig) => Interpolation.T c (b -> a) -> [b -> a] -> c -> b -> sig c -> sig b -> sig a shapeFreqModSample ip waves shape0 phase shapes freqs = SigG.zipWith ($) (Interpolation.multiRelativeConstantPad ip shape0 shapes waves) (freqToPhase phase freqs) {- GNUPlot.plotList [] $ take 500 $ shapeFreqModSample Interpolation.cubic (SigG.map Wave.truncOddCosine [0..3]) (0.1::Double) (0::Double) (repeat 0.005) (repeat 0.02) -} {- | Time stretching and frequency modulation of a pure tone. We consider a tone as the result of a shape modulated oscillator, and virtually reconstruct the waveform function (a function of time and phase) by interpolation and resample it. This way we can alter frequency and time progress of the tone independently. This function is identical to using 'shapeFreqMod' with a wave function constructed by 'Wave.sampledTone' but it consumes the sampled source tone lazily and thus allows only relative shape control with non-negative control steps. The function is similar to 'shapeFreqModSample' but respects that in a sampled tone, phase and shape control advance synchronously. Actually we could re-use 'shapeFreqModSample' with modified phase values. But we would have to cope with negative shape control jumps, and waves would be padded locally cyclically. The latter one is not wanted since we want padding according to the adjacencies in the source tone. Although the shape difference values must be non-negative I hesitate to give them the type @Number.NonNegative.T t@ because then you cannot call this function with other types of non-negative numbers like 'Number.NonNegativeChunky.T'. The prototype tone signal is reproduced if @freqs == repeat (1\/period)@ and @shapes == repeat 1@. -} shapeFreqModFromSampledTone :: (RealField.C t, Sample.C a, SigG.C sig) => Interpolation.T t y -> Interpolation.T t y -> t -> sig y -> t -> t -> sig t -> sig t -> sig y shapeFreqModFromSampledTone ipLeap ipStep period sampledTone shape0 phase shapes freqs = SigG.map (uncurry (ToneMod.interpolateCell ipLeap ipStep)) (ToneMod.oscillatorCells ipLeap ipStep period sampledTone (shape0, shapes) (phase, freqs)) {- GNUPlot.plotList [] $ take 1000 $ shapeFreqModFromSampledTone Interpolation.linear Interpolation.linear (1/0.07::Double) (staticSine (0::Double) 0.07) 0 0 (repeat 0.1) (repeat 0.01) GNUPlot.plotList [] $ take 1000 $ shapeFreqModFromSampledTone Interpolation.linear Interpolation.linear (1/0.07::Double) (staticSine (0::Double) 0.07) 0 0 (repeat 0.1) (SigG.iterate (*(1-2e-3)) 0.01) GNUPlot.plotList [] $ take 101 $ shapeFreqModFromSampledTone Interpolation.linear Interpolation.linear (1/0.07::Double) (SigG.iterate (1+) (0::Double)) 0 0 (repeat 1) (repeat 0.7) -} -} {- * Oscillators with specific waveforms -} {- | sine oscillator with static frequency -} staticSine :: (Trans.C a, RealField.C a, Sample.C a, SigG.C sig) => Phase.T a -> a -> sig a staticSine = static Wave.sine {- | sine oscillator with modulated frequency -} freqModSine :: (Trans.C a, RealField.C a, Sample.C a, SigG.C sig) => Phase.T a -> sig a -> sig a freqModSine = freqMod Wave.sine {- | sine oscillator with modulated phase, useful for FM synthesis -} phaseModSine :: (Trans.C a, RealField.C a, Sample.C a, SigG.C sig) => a -> sig a -> sig a phaseModSine = phaseMod Wave.sine {- | saw tooth oscillator with modulated frequency -} staticSaw :: (RealField.C a, Sample.C a, SigG.C sig) => Phase.T a -> a -> sig a staticSaw = static Wave.saw {- | saw tooth oscillator with modulated frequency -} freqModSaw :: (RealField.C a, Sample.C a, SigG.C sig) => Phase.T a -> sig a -> sig a freqModSaw = freqMod Wave.saw