-- | Sample and hold module Sound.SC3.UGen.Record.Latch where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data Latch = Latch { rate :: S.Rate, input :: S.UGen, trig :: S.UGen } deriving (Show) latch :: Latch latch = Latch { rate = S.AR, input = 0.0, trig = 0.0 } mkLatch :: Latch -> S.UGen mkLatch (Latch r a' b') = S.mkOsc r "Latch" [a',b'] 1 instance Make Latch where ugen = mkLatch