-- | (Undocumented class) module Sound.SC3.UGen.Record.PV_ExtractRepeat where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data PV_ExtractRepeat = PV_ExtractRepeat { buffer :: S.UGen, loopbuf :: S.UGen, loopdur :: S.UGen, memorytime :: S.UGen, which :: S.UGen, ffthop :: S.UGen, thresh :: S.UGen } deriving (Show) pv_ExtractRepeat :: PV_ExtractRepeat pv_ExtractRepeat = PV_ExtractRepeat { buffer = 0.0, loopbuf = 0.0, loopdur = 0.0, memorytime = 30.0, which = 0.0, ffthop = 0.5, thresh = 1.0 } mkPV_ExtractRepeat :: PV_ExtractRepeat -> S.UGen mkPV_ExtractRepeat (PV_ExtractRepeat a' b' c' d' e' f' g') = S.mkOsc S.KR "PV_ExtractRepeat" [a',b',c',d',e',f',g'] 1 instance Make PV_ExtractRepeat where ugen = mkPV_ExtractRepeat