{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NoIncoherentInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NoUndecidableInstances #-}
module Vivid.UGens.SynthControl (
   
     
   
     freeSelf
   ) where
import Vivid.UGens.Args
import Vivid.SC.SynthDef.Types (CalculationRate(..))
import Vivid.SynthDef
import Vivid.SynthDef.FromUA
   
freeSelf :: Args '["trigger"] '[] a => a -> SDBody a Signal
freeSelf :: forall a. Args '["trigger"] '[] a => a -> SDBody a Signal
freeSelf = String
-> CalculationRate
-> Vs '["trigger"]
-> NoDefaults (SDBodyArgs a)
-> a
-> StateT
     ([Int], SynthDef (SDBodyArgs a), VarSet (SDBodyArgs a))
     Identity
     Signal
forall (tags :: [Symbol]) optional userSupplied (args :: [Symbol]).
(GetSymbolVals (Vs tags), FromUA optional, FromUA userSupplied,
 SDBodyArgs optional ~ SDBodyArgs userSupplied,
 SDBodyArgs optional ~ args) =>
String
-> CalculationRate
-> Vs tags
-> optional
-> userSupplied
-> SDBody' args Signal
makeUGen
   String
"FreeSelf" CalculationRate
KR
   (Vs '["trigger"]
forall (a :: [Symbol]). Vs a
Vs::Vs '["trigger"])
   NoDefaults (SDBodyArgs a)
forall (args :: [Symbol]). NoDefaults args
NoDefaults