-- | Formant oscillator module Sound.SC3.UGen.Record.Formant where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data Formant = Formant { fundfreq :: S.UGen, formfreq :: S.UGen, bwfreq :: S.UGen } deriving (Show) formant :: Formant formant = Formant { fundfreq = 440.0, formfreq = 1760.0, bwfreq = 880.0 } mkFormant :: Formant -> S.UGen mkFormant (Formant a' b' c') = S.mkOsc S.AR "Formant" [a',b',c'] 1 instance Make Formant where ugen = mkFormant