{-# LANGUAGE NoImplicitPrelude #-} {- | Copyright : (c) Henning Thielemann 2006, 2008 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes Tone generators -} module Synthesizer.Physical.Oscillator where import qualified Synthesizer.SampleRateContext.Oscillator as OsciC -- import qualified Synthesizer.Plain.Oscillator as Osci import qualified Synthesizer.Basic.Wave as Wave import qualified Synthesizer.Physical.Signal as SigP import qualified Algebra.OccasionallyScalar as OccScalar import qualified Algebra.Module as 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 PreludeBase -- import NumericPrelude {- * Oscillators with constant waveforms -} {- | oscillator with a functional waveform with constant frequency -} static :: (RealField.C t, Field.C t', OccScalar.C t t') => Wave.T t yv -> (t' -> y' -> t -> t' -> SigP.T t t' y y' yv) static wave sampleRate amplitude phase freq = SigP.lift0 (OsciC.static wave amplitude phase freq) sampleRate {- | oscillator with a functional waveform with modulated frequency -} freqMod :: (RealField.C t, Field.C t', OccScalar.C t t') => Wave.T t yv -> (y' -> t -> SigP.T t t' t t' t -> SigP.T t t' y y' yv) freqMod wave amplitude phase = SigP.lift1 (OsciC.freqMod wave amplitude phase) {- | sine oscillator with static frequency -} staticSine :: (RealField.C a, Trans.C a, Field.C t', OccScalar.C a t') => t' -> y' -> a -> t' -> SigP.T a t' a y' a staticSine = static Wave.sine {- | sine oscillator with modulated frequency -} freqModSine :: (RealField.C a, Trans.C a, Module.C a a, Field.C t', OccScalar.C a t') => y' -> a -> SigP.T a t' a t' a -> SigP.T a t' a y' a freqModSine = freqMod Wave.sine {- | saw tooth oscillator with modulated frequency -} staticSaw :: (RealField.C a, Field.C t', OccScalar.C a t') => t' -> y' -> a -> t' -> SigP.T a t' a y' a staticSaw = static Wave.saw {- | saw tooth oscillator with modulated frequency -} freqModSaw :: (RealField.C a, Field.C t', Module.C a a, OccScalar.C a t') => y' -> a -> SigP.T a t' a t' a -> SigP.T a t' a y' a freqModSaw = freqMod Wave.saw