-- | Pass bins above a threshold. module Sound.SC3.UGen.Record.PV_MagAbove where import qualified Sound.SC3.UGen as S import Sound.SC3.UGen.Record data PV_MagAbove = PV_MagAbove { buffer :: S.UGen, threshold :: S.UGen } deriving (Show) pv_MagAbove :: PV_MagAbove pv_MagAbove = PV_MagAbove { buffer = 0.0, threshold = 0.0 } mkPV_MagAbove :: PV_MagAbove -> S.UGen mkPV_MagAbove (PV_MagAbove a' b') = S.mkOsc S.KR "PV_MagAbove" [a',b'] 1 instance Make PV_MagAbove where ugen = mkPV_MagAbove