module Sound.SC3.UGen.Record.PV_RectComb where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data PV_RectComb = PV_RectComb { buffer :: S.UGen, numTeeth :: S.UGen, phase :: S.UGen, width :: S.UGen } deriving (Show) pV_RectComb :: PV_RectComb pV_RectComb = PV_RectComb { buffer = 0.0, numTeeth = 0.0, phase = 0.0, width = 0.5 } mkPV_RectComb :: PV_RectComb -> S.UGen mkPV_RectComb (PV_RectComb a' b' c' d') = S.mkOsc S.KR "PV_RectComb" [a',b',c',d'] 1 instance Make PV_RectComb where ugen = mkPV_RectComb