-- | Pulse counter. module Sound.SC3.UGen.Record.PulseCount where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data PulseCount = PulseCount { rate :: S.Rate, trig :: S.UGen, reset :: S.UGen } deriving (Show) pulseCount :: PulseCount pulseCount = PulseCount { rate = S.AR, trig = 0.0, reset = 0.0 } mkPulseCount :: PulseCount -> S.UGen mkPulseCount (PulseCount r a' b') = S.mkOsc r "PulseCount" [a',b'] 1 instance Make PulseCount where ugen = mkPulseCount