{-# LANGUAGE DataKinds #-}

{-# LANGUAGE NoIncoherentInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NoUndecidableInstances #-}

module Vivid.UGens.SynthControl (
   -- Might not actually need these 2 directly:
---     control
---   , controlName

     -- In Vivid.UGens.Analysis:
   -- , detectSilence
---   , done
---   , free__
     freeSelf
---   , freeSelfWhenDone
---   , lagControl
---   , namedControl
---   , pause
---   , pauseSelf
---   , pauseSelfWhenDone
---   , trigControl
   ) where

import Vivid.UGens.Args
import Vivid.SC.SynthDef.Types (CalculationRate(..))
import Vivid.SynthDef
import Vivid.SynthDef.FromUA

   -- Might not actually need these 2 directly:
--- control ::
--- control =
--- controlName ::
--- controlName =

--- done ::
--- done =
--- free__ ::
--- free__ =

-- | Frees the synth when the trigger changes from non-positive to positive
-- 
--   Runs at 'KR'
freeSelf :: Args '["trigger"] '[] a => a -> SDBody a Signal
freeSelf :: a -> SDBody a Signal
freeSelf = String
-> CalculationRate
-> Vs '["trigger"]
-> NoDefaults (SDBodyArgs a)
-> a
-> SDBody a 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

--- freeSelfWhenDone ::
--- freeSelfWhenDone =

--- lagControl ::
--- lagControl =
--- namedControl ::
--- namedControl =
--- pause ::
--- pause =
--- pauseSelf ::
--- pauseSelf =
--- pauseSelfWhenDone ::
--- pauseSelfWhenDone =
--- trigControl ::
--- trigControl =