-- | Print the current output value of a demand rate UGen module Sound.SC3.UGen.Record.Dpoll where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data Dpoll = Dpoll { input :: S.UGen, label_ :: S.UGen, run :: S.UGen, trigid :: S.UGen } deriving (Show) dpoll :: Dpoll dpoll = Dpoll { input = 0.0, label_ = 0.0, run = 1.0, trigid = -1.0 } mkDpoll :: Dpoll -> S.UGen mkDpoll (Dpoll a' b' c' d') = S.mkOsc S.DR "Dpoll" [a',b',c',d'] 1 instance Make Dpoll where ugen = mkDpoll