-- | (Undocumented class)
module Sound.SC3.UGen.Record.StkSaxofony where
import qualified Sound.SC3.UGen as S
import Sound.SC3.UGen.Record
data StkSaxofony = StkSaxofony {
  rate :: S.Rate,
  freq :: S.UGen,
  reedstiffness :: S.UGen,
  reedaperture :: S.UGen,
  noisegain :: S.UGen,
  blowposition :: S.UGen,
  vibratofrequency :: S.UGen,
  vibratogain :: S.UGen,
  breathpressure :: S.UGen,
  trig :: S.UGen
  } deriving (Show)
stkSaxofony :: StkSaxofony
stkSaxofony = StkSaxofony {
  rate = S.AR,
  freq = 220.0,
  reedstiffness = 64.0,
  reedaperture = 64.0,
  noisegain = 20.0,
  blowposition = 26.0,
  vibratofrequency = 20.0,
  vibratogain = 20.0,
  breathpressure = 128.0,
  trig = 1.0
  }
mkStkSaxofony :: StkSaxofony -> S.UGen
mkStkSaxofony (StkSaxofony r a' b' c' d' e' f' g' h' i') = S.mkOsc r "StkSaxofony" [a',b',c',d',e',f',g',h',i'] 1
instance Make StkSaxofony where
  ugen = mkStkSaxofony