-- | (Undocumented class)
module Sound.SC3.UGen.Record.VBAP where
import qualified Sound.SC3.UGen as S
import Sound.SC3.UGen.Record
data VBAP = VBAP {
  rate :: S.Rate,
  input :: S.UGen,
  bufnum :: S.UGen,
  azimuth :: S.UGen,
  elevation :: S.UGen,
  spread :: S.UGen
  } deriving (Show)
vBAP :: VBAP
vBAP = VBAP {
  rate = S.AR,
  input = 0.0,
  bufnum = 0.0,
  azimuth = 0.0,
  elevation = 1.0,
  spread = 0.0
  }
mkVBAP :: VBAP -> S.UGen
mkVBAP (VBAP r a' b' c' d' e') = S.mkOsc r "VBAP" [a',b',c',d',e'] undefined
instance Make VBAP where
  ugen = mkVBAP