{-# LANGUAGE NoImplicitPrelude #-} {- | Copyright : (c) Henning Thielemann 2006 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes Tone generators -} module Synthesizer.FusionList.Oscillator where import qualified Synthesizer.Basic.Wave as Wave import qualified Synthesizer.Basic.Phase as Phase import qualified Synthesizer.FusionList.Signal as Sig -- import qualified Synthesizer.FusionList.Interpolation as Interpolation {- 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 NumericPrelude import qualified Prelude as P import PreludeBase {- * Oscillators with arbitrary but constant waveforms -} {-# INLINE freqToPhase #-} {- | Convert a list of phase steps into a list of momentum phases phase is a number in the interval [0,1) freq contains the phase steps -} freqToPhase :: RealField.C a => Phase.T a -> Sig.T a -> Sig.T (Phase.T a) freqToPhase phase freq = Sig.scanL (flip Phase.increment) phase freq {- Inlining blocks fusion of map and iterate - on the other hand it enables fusion in the main program -} {-# INLINE static #-} {- | oscillator with constant frequency -} static :: (RealField.C a) => Wave.T a b -> (Phase.T a -> a -> Sig.T b) static wave phase freq = Sig.map (Wave.apply wave) (Sig.iterate (Phase.increment freq) phase) {-# INLINE phaseMod #-} {- | oscillator with modulated phase -} phaseMod :: (RealField.C a) => Wave.T a b -> a -> Sig.T a -> Sig.T b phaseMod wave = shapeMod (Wave.phaseOffset wave) zero {-# INLINE shapeMod #-} {- | oscillator with modulated shape -} shapeMod :: (RealField.C a) => (c -> Wave.T a b) -> Phase.T a -> a -> Sig.T c -> Sig.T b shapeMod wave phase freq parameters = Sig.zipWith (Wave.apply . wave) parameters (Sig.iterate (Phase.increment freq) phase) {-# INLINE freqMod #-} {- | oscillator with modulated frequency -} freqMod :: (RealField.C a) => Wave.T a b -> Phase.T a -> Sig.T a -> Sig.T b freqMod wave phase freqs = Sig.map (Wave.apply wave) (freqToPhase phase freqs) {-# INLINE phaseFreqMod #-} {- | oscillator with both phase and frequency modulation -} phaseFreqMod :: (RealField.C a) => Wave.T a b -> Sig.T a -> Sig.T a -> Sig.T b phaseFreqMod wave = shapeFreqMod (Wave.phaseOffset wave) zero {-# INLINE shapeFreqMod #-} {- | oscillator with both shape and frequency modulation -} shapeFreqMod :: (RealField.C a) => (c -> Wave.T a b) -> Phase.T a -> Sig.T c -> Sig.T a -> Sig.T b shapeFreqMod wave phase parameters freqs = Sig.zipWith (Wave.apply . wave) parameters (freqToPhase phase freqs) {- {- | oscillator with a sampled waveform with constant frequency This essentially an interpolation with cyclic padding. -} {-# INLINE staticSample #-} staticSample :: RealField.C a => Interpolation.T a b -> Sig.T b -> Phase.T a -> a -> Sig.T b staticSample ip wave phase freq = freqModSample ip wave phase (Sig.repeat freq) {- | oscillator with a sampled waveform with modulated frequency Should behave homogenously for different types of interpolation. -} {-# INLINE freqModSample #-} freqModSample :: RealField.C a => Interpolation.T a b -> Sig.T b -> Phase.T a -> Sig.T a -> Sig.T b freqModSample ip wave phase freqs = let len = Sig.length wave in Interpolation.multiRelativeCyclicPad ip (fromIntegral len * Phase.toRepresentative phase) (Sig.map (* fromIntegral len) freqs) wave -} {- * Oscillators with specific waveforms -} {-# INLINE staticSine #-} {- | sine oscillator with static frequency -} staticSine :: (Trans.C a, RealField.C a) => Phase.T a -> a -> Sig.T a staticSine = static Wave.sine {-# INLINE freqModSine #-} {- | sine oscillator with modulated frequency -} freqModSine :: (Trans.C a, RealField.C a) => Phase.T a -> Sig.T a -> Sig.T a freqModSine = freqMod Wave.sine {-# INLINE phaseModSine #-} {- | sine oscillator with modulated phase, useful for FM synthesis -} phaseModSine :: (Trans.C a, RealField.C a) => a -> Sig.T a -> Sig.T a phaseModSine = phaseMod Wave.sine {-# INLINE staticSaw #-} {- | saw tooth oscillator with modulated frequency -} staticSaw :: RealField.C a => Phase.T a -> a -> Sig.T a staticSaw = static Wave.saw {-# INLINE freqModSaw #-} {- | saw tooth oscillator with modulated frequency -} freqModSaw :: RealField.C a => Phase.T a -> Sig.T a -> Sig.T a freqModSaw = freqMod Wave.saw