{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NoIncoherentInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NoUndecidableInstances #-}
module Vivid.UGens.Random (
      
   
   
     expRand
     
   
   , linRand
   , rand
     
   
   
     
   
   
   
   
   
   
   ) where
import Vivid.SC.SynthDef.Types (CalculationRate(..))
import Vivid.SynthDef
import Vivid.SynthDef.FromUA
import Vivid.UGens.Args
expRand :: (Args '[] '["lo","hi"] a) => a -> SDBody a Signal
expRand :: forall a. Args '[] '["lo", "hi"] a => a -> SDBody a Signal
expRand = String
-> CalculationRate
-> Vs '["lo", "hi"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (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
"ExpRand" CalculationRate
IR
   (Vs '["lo", "hi"]
forall (a :: [Symbol]). Vs a
Vs::Vs '["lo", "hi"])
   (Float -> UA "lo" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "lo" as
lo_ (Float
0::Float), Float -> UA "hi" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "hi" as
hi_ (Float
1::Float))
linRand :: (Args '[] '["lo","hi","minmax"] a) => a -> SDBody a Signal
linRand :: forall a.
Args '[] '["lo", "hi", "minmax"] a =>
a -> SDBody a Signal
linRand = String
-> CalculationRate
-> Vs '["lo", "hi", "minmax"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (SDBodyArgs a),
    UA "minmax" (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
"LinRand" CalculationRate
IR
   (Vs '["lo", "hi", "minmax"]
forall (a :: [Symbol]). Vs a
Vs::Vs '["lo", "hi", "minmax"])
   (Float -> UA "lo" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "lo" as
lo_ (Float
0::Float), Float -> UA "hi" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "hi" as
hi_ (Float
1::Float), Float -> UA "minmax" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "minmax" as
minmax_ (Float
0::Float))
rand :: (Args '[] '["lo","hi"] a) => a -> SDBody a Signal
rand :: forall a. Args '[] '["lo", "hi"] a => a -> SDBody a Signal
rand = String
-> CalculationRate
-> Vs '["lo", "hi"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (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
"Rand" CalculationRate
IR
   (Vs '["lo", "hi"]
forall (a :: [Symbol]). Vs a
Vs::Vs '["lo", "hi"])
   (Float -> UA "lo" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "lo" as
lo_ (Float
0::Float), Float -> UA "hi" (SDBodyArgs a)
forall s (as :: [Symbol]). ToSig s as => s -> UA "hi" as
hi_ (Float
1::Float))