-- | (Undocumented class) module Sound.SC3.UGen.Record.Decimator where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data Decimator = Decimator { input :: S.UGen, rate_ :: S.UGen, bits :: S.UGen } deriving (Show) decimator :: Decimator decimator = Decimator { input = 0.0, rate_ = 44100.0, bits = 24.0 } mkDecimator :: Decimator -> S.UGen mkDecimator (Decimator a' b' c') = S.mkOsc S.AR "Decimator" [a',b',c'] 1 instance Make Decimator where ugen = mkDecimator