-- | For if you want a SynthDef where each Synth instance has a new random number.
-- 
--   Creates a random value between \"lo\" and \"hi\". The value never changes in
--   the synth.
-- 
--   These compute at "IR"

{-# LANGUAGE DataKinds #-}

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

module Vivid.UGens.Random (
      -- In Vivid.UGens.Demand:
   --   dshuf
   -- , dwrand
     expRand
     -- In Vivid.UGens.Filters:
   -- , hasher
---   , iRand
   , linRand
---   , nRand
   , rand
     -- In Vivid.UGens.Generators.Stochastic:
   -- , randID
   -- , randSeed
     -- in UGens.Triggers:
   -- , tChoose
   -- , tExpRand
   -- , tIRand
   -- , tRand
   -- , tWChoose
   -- , tWIndex
   ) 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 :: a -> SDBody a Signal
expRand = String
-> CalculationRate
-> Vs '["lo", "hi"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (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
"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))

--- iRand ::
--- iRand =

linRand :: (Args '[] '["lo","hi","minmax"] a) => a -> SDBody a Signal
linRand :: a -> SDBody a Signal
linRand = String
-> CalculationRate
-> Vs '["lo", "hi", "minmax"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (SDBodyArgs a),
    UA "minmax" (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
"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))

--- nRand ::
--- nRand =

rand :: (Args '[] '["lo","hi"] a) => a -> SDBody a Signal
rand :: a -> SDBody a Signal
rand = String
-> CalculationRate
-> Vs '["lo", "hi"]
-> (UA "lo" (SDBodyArgs a), UA "hi" (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
"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))