-- | Random (Noise) Generators
module CsoundExpr.Opcodes.Siggen.Noise
    (bexprndA',
     bexprndA,
     bexprndI',
     bexprndI,
     bexprndK',
     bexprndK,
     cauchyA',
     cauchyA,
     cauchyI',
     cauchyI,
     cauchyK',
     cauchyK,
     cuserrndA',
     cuserrndA,
     cuserrndI',
     cuserrndI,
     cuserrndK',
     cuserrndK,
     duserrndA',
     duserrndA,
     duserrndI',
     duserrndI,
     duserrndK',
     duserrndK,
     exprandA',
     exprandA,
     exprandI',
     exprandI,
     exprandK',
     exprandK,
     gaussA',
     gaussA,
     gaussI',
     gaussI,
     gaussK',
     gaussK,
     linrandA',
     linrandA,
     linrandI',
     linrandI,
     linrandK',
     linrandK,
     noise',
     noise,
     pcauchyA',
     pcauchyA,
     pcauchyI',
     pcauchyI,
     pcauchyK',
     pcauchyK,
     pinkish',
     pinkish,
     poissonA',
     poissonA,
     poissonI',
     poissonI,
     poissonK',
     poissonK,
     randA,
     randK,
     randhA,
     randhK,
     randiA,
     randiK,
     rnd31A',
     rnd31A,
     rnd31I',
     rnd31I,
     rnd31K',
     rnd31K,
     randomA',
     randomA,
     randomI',
     randomI,
     randomK',
     randomK,
     randomhA',
     randomhA,
     randomhK',
     randomhK,
     randomiA',
     randomiA,
     randomiK',
     randomiK,
     trirandA',
     trirandA,
     trirandI',
     trirandI,
     trirandK',
     trirandK,
     unirandA',
     unirandA,
     unirandI',
     unirandI,
     unirandK',
     unirandK,
     urdA',
     urdA,
     urdI',
     urdI,
     urdK',
     urdK,
     weibullA',
     weibullA,
     weibullI',
     weibullI,
     weibullK',
     weibullK,
     jitter',
     jitter,
     jitter2',
     jitter2,
     trandom',
     trandom)
where



import CsoundExpr.Base.Types
import CsoundExpr.Base.MultiOut
import CsoundExpr.Base.SideEffect
import CsoundExpr.Base.UserDefined



-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndA' :: (K k0) => k0 -> Arate
bexprndA' k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndA :: (K k0) => k0 -> SideEffect Arate
bexprndA k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndI' :: (K k0) => k0 -> Irate
bexprndI' k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndI :: (K k0) => k0 -> SideEffect Irate
bexprndI k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndK' :: (K k0) => k0 -> Krate
bexprndK' k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : bexprnd
--  
--  
-- * syntax : 
--  
--  >   ares bexprnd krange
--  >   ires bexprnd krange
--  >   kres bexprnd krange
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bexprnd.html>
 
bexprndK :: (K k0) => k0 -> SideEffect Krate
bexprndK k0range = opcode "bexprnd" args
  where args = [to k0range]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyA' :: (K k0) => k0 -> Arate
cauchyA' k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyA :: (K k0) => k0 -> SideEffect Arate
cauchyA k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyI' :: (K k0) => k0 -> Irate
cauchyI' k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyI :: (K k0) => k0 -> SideEffect Irate
cauchyI k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyK' :: (K k0) => k0 -> Krate
cauchyK' k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cauchy
--  
--  
-- * syntax : 
--  
--  >   ares cauchy kalpha
--  >   ires cauchy kalpha
--  >   kres cauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator. This is an x-class
-- noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cauchy.html>
 
cauchyK :: (K k0) => k0 -> SideEffect Krate
cauchyK k0alpha = opcode "cauchy" args
  where args = [to k0alpha]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndA' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Arate
cuserrndA' k0min k1max k2tableNum = opcode "cuserrnd" args
  where args = [to k0min, to k1max, to k2tableNum]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndA ::
            (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Arate
cuserrndA k0min k1max k2tableNum = opcode "cuserrnd" args
  where args = [to k0min, to k1max, to k2tableNum]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndI' :: Irate -> Irate -> Irate -> Irate
cuserrndI' i0min i1max i2tableNum = opcode "cuserrnd" args
  where args = [to i0min, to i1max, to i2tableNum]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndI :: Irate -> Irate -> Irate -> SideEffect Irate
cuserrndI i0min i1max i2tableNum = opcode "cuserrnd" args
  where args = [to i0min, to i1max, to i2tableNum]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndK' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Krate
cuserrndK' k0min k1max k2tableNum = opcode "cuserrnd" args
  where args = [to k0min, to k1max, to k2tableNum]


-- | * opcode : cuserrnd
--  
--  
-- * syntax : 
--  
--  >   aout cuserrnd kmin, kmax, ktableNum
--  >   iout cuserrnd imin, imax, itableNum
--  >   kout cuserrnd kmin, kmax, ktableNum
--  
--  
-- * description : 
--  
--  Continuous USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cuserrnd.html>
 
cuserrndK ::
            (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Krate
cuserrndK k0min k1max k2tableNum = opcode "cuserrnd" args
  where args = [to k0min, to k1max, to k2tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndA' :: (K k0) => k0 -> Arate
duserrndA' k0tableNum = opcode "duserrnd" args
  where args = [to k0tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndA :: (K k0) => k0 -> SideEffect Arate
duserrndA k0tableNum = opcode "duserrnd" args
  where args = [to k0tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndI' :: Irate -> Irate
duserrndI' i0tableNum = opcode "duserrnd" args
  where args = [to i0tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndI :: Irate -> SideEffect Irate
duserrndI i0tableNum = opcode "duserrnd" args
  where args = [to i0tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndK' :: (K k0) => k0 -> Krate
duserrndK' k0tableNum = opcode "duserrnd" args
  where args = [to k0tableNum]


-- | * opcode : duserrnd
--  
--  
-- * syntax : 
--  
--  >   aout duserrnd ktableNum
--  >   iout duserrnd itableNum
--  >   kout duserrnd ktableNum
--  
--  
-- * description : 
--  
--  Discrete USER-defined-distribution RaNDom generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/duserrnd.html>
 
duserrndK :: (K k0) => k0 -> SideEffect Krate
duserrndK k0tableNum = opcode "duserrnd" args
  where args = [to k0tableNum]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandA' :: (K k0) => k0 -> Arate
exprandA' k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandA :: (K k0) => k0 -> SideEffect Arate
exprandA k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandI' :: (K k0) => k0 -> Irate
exprandI' k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandI :: (K k0) => k0 -> SideEffect Irate
exprandI k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandK' :: (K k0) => k0 -> Krate
exprandK' k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : exprand
--  
--  
-- * syntax : 
--  
--  >   ares exprand klambda
--  >   ires exprand klambda
--  >   kres exprand klambda
--  
--  
-- * description : 
--  
--  Exponential distribution random number generator (positive
-- values only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/exprand.html>
 
exprandK :: (K k0) => k0 -> SideEffect Krate
exprandK k0lambda = opcode "exprand" args
  where args = [to k0lambda]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussA' :: (K k0) => k0 -> Arate
gaussA' k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussA :: (K k0) => k0 -> SideEffect Arate
gaussA k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussI' :: (K k0) => k0 -> Irate
gaussI' k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussI :: (K k0) => k0 -> SideEffect Irate
gaussI k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussK' :: (K k0) => k0 -> Krate
gaussK' k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : gauss
--  
--  
-- * syntax : 
--  
--  >   ares gauss krange
--  >   ires gauss krange
--  >   kres gauss krange
--  
--  
-- * description : 
--  
--  Gaussian distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gauss.html>
 
gaussK :: (K k0) => k0 -> SideEffect Krate
gaussK k0range = opcode "gauss" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandA' :: (K k0) => k0 -> Arate
linrandA' k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandA :: (K k0) => k0 -> SideEffect Arate
linrandA k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandI' :: (K k0) => k0 -> Irate
linrandI' k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandI :: (K k0) => k0 -> SideEffect Irate
linrandI k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandK' :: (K k0) => k0 -> Krate
linrandK' k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : linrand
--  
--  
-- * syntax : 
--  
--  >   ares linrand krange
--  >   ires linrand krange
--  >   kres linrand krange
--  
--  
-- * description : 
--  
--  Linear distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/linrand.html>
 
linrandK :: (K k0) => k0 -> SideEffect Krate
linrandK k0range = opcode "linrand" args
  where args = [to k0range]


-- | * opcode : noise
--  
--  
-- * syntax : 
--  
--  >   ares noise xamp, kbeta
--  
--  
-- * description : 
--  
--  A white noise generator with an IIR lowpass filter.
--  
--  
-- * url : <http://www.csounds.com/manual/html/noise.html>
 
noise' :: (X x0, K k0) => x0 -> k0 -> Arate
noise' x0amp k1beta = opcode "noise" args
  where args = [to x0amp, to k1beta]


-- | * opcode : noise
--  
--  
-- * syntax : 
--  
--  >   ares noise xamp, kbeta
--  
--  
-- * description : 
--  
--  A white noise generator with an IIR lowpass filter.
--  
--  
-- * url : <http://www.csounds.com/manual/html/noise.html>
 
noise :: (X x0, K k0) => x0 -> k0 -> SideEffect Arate
noise x0amp k1beta = opcode "noise" args
  where args = [to x0amp, to k1beta]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyA' :: (K k0) => k0 -> Arate
pcauchyA' k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyA :: (K k0) => k0 -> SideEffect Arate
pcauchyA k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyI' :: (K k0) => k0 -> Irate
pcauchyI' k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyI :: (K k0) => k0 -> SideEffect Irate
pcauchyI k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyK' :: (K k0) => k0 -> Krate
pcauchyK' k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pcauchy
--  
--  
-- * syntax : 
--  
--  >   ares pcauchy kalpha
--  >   ires pcauchy kalpha
--  >   kres pcauchy kalpha
--  
--  
-- * description : 
--  
--  Cauchy distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pcauchy.html>
 
pcauchyK :: (K k0) => k0 -> SideEffect Krate
pcauchyK k0alpha = opcode "pcauchy" args
  where args = [to k0alpha]


-- | * opcode : pinkish
--  
--  
-- * syntax : 
--  
--  >   ares pinkish xin [, imethod] [, inumbands] [, iseed] [, iskip]
--  
--  
-- * description : 
--  
--  Generates approximate pink noise (-3dB/oct response) by one of
-- two different methods:
--  
--  
-- * url : <http://www.csounds.com/manual/html/pinkish.html>
 
pinkish' :: (X x0) => [Irate] -> x0 -> Arate
pinkish' i0init x1in = opcode "pinkish" args
  where args = [to x1in] ++ map to i0init


-- | * opcode : pinkish
--  
--  
-- * syntax : 
--  
--  >   ares pinkish xin [, imethod] [, inumbands] [, iseed] [, iskip]
--  
--  
-- * description : 
--  
--  Generates approximate pink noise (-3dB/oct response) by one of
-- two different methods:
--  
--  
-- * url : <http://www.csounds.com/manual/html/pinkish.html>
 
pinkish :: (X x0) => [Irate] -> x0 -> SideEffect Arate
pinkish i0init x1in = opcode "pinkish" args
  where args = [to x1in] ++ map to i0init


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonA' :: (K k0) => k0 -> Arate
poissonA' k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonA :: (K k0) => k0 -> SideEffect Arate
poissonA k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonI' :: (K k0) => k0 -> Irate
poissonI' k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonI :: (K k0) => k0 -> SideEffect Irate
poissonI k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonK' :: (K k0) => k0 -> Krate
poissonK' k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : poisson
--  
--  
-- * syntax : 
--  
--  >   ares poisson klambda
--  >   ires poisson klambda
--  >   kres poisson klambda
--  
--  
-- * description : 
--  
--  Poisson distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poisson.html>
 
poissonK :: (K k0) => k0 -> SideEffect Krate
poissonK k0lambda = opcode "poisson" args
  where args = [to k0lambda]


-- | * opcode : rand
--  
--  
-- * syntax : 
--  
--  >   ares rand xamp [, iseed] [, isel] [, ioffset]
--  >   kres rand xamp [, iseed] [, isel] [, ioffset]
--  
--  
-- * description : 
--  
--  Output is a controlled random number series between -amp and
-- +amp
--  
--  
-- * url : <http://www.csounds.com/manual/html/rand.html>
 
randA :: (X x0) => [Irate] -> x0 -> Arate
randA i0init x1amp = opcode "rand" args
  where args = [to x1amp] ++ map to i0init


-- | * opcode : rand
--  
--  
-- * syntax : 
--  
--  >   ares rand xamp [, iseed] [, isel] [, ioffset]
--  >   kres rand xamp [, iseed] [, isel] [, ioffset]
--  
--  
-- * description : 
--  
--  Output is a controlled random number series between -amp and
-- +amp
--  
--  
-- * url : <http://www.csounds.com/manual/html/rand.html>
 
randK :: (X x0) => [Irate] -> x0 -> Krate
randK i0init x1amp = opcode "rand" args
  where args = [to x1amp] ++ map to i0init


-- | * opcode : randh
--  
--  
-- * syntax : 
--  
--  >   ares randh xamp, xcps [, iseed] [, isize] [, ioffset]
--  >   kres randh kamp, kcps [, iseed] [, isize] [, ioffset]
--  
--  
-- * description : 
--  
--  Generates random numbers and holds them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randh.html>
 
randhA :: (X x0, X x1) => [Irate] -> x0 -> x1 -> Arate
randhA i0init x1amp x2cps = opcode "randh" args
  where args = [to x1amp, to x2cps] ++ map to i0init


-- | * opcode : randh
--  
--  
-- * syntax : 
--  
--  >   ares randh xamp, xcps [, iseed] [, isize] [, ioffset]
--  >   kres randh kamp, kcps [, iseed] [, isize] [, ioffset]
--  
--  
-- * description : 
--  
--  Generates random numbers and holds them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randh.html>
 
randhK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Krate
randhK i0init k1amp k2cps = opcode "randh" args
  where args = [to k1amp, to k2cps] ++ map to i0init


-- | * opcode : randi
--  
--  
-- * syntax : 
--  
--  >   ares randi xamp, xcps [, iseed] [, isize] [, ioffset]
--  >   kres randi kamp, kcps [, iseed] [, isize] [, ioffset]
--  
--  
-- * description : 
--  
--  Generates a controlled random number series with interpolation
-- between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randi.html>
 
randiA :: (X x0, X x1) => [Irate] -> x0 -> x1 -> Arate
randiA i0init x1amp x2cps = opcode "randi" args
  where args = [to x1amp, to x2cps] ++ map to i0init


-- | * opcode : randi
--  
--  
-- * syntax : 
--  
--  >   ares randi xamp, xcps [, iseed] [, isize] [, ioffset]
--  >   kres randi kamp, kcps [, iseed] [, isize] [, ioffset]
--  
--  
-- * description : 
--  
--  Generates a controlled random number series with interpolation
-- between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randi.html>
 
randiK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Krate
randiK i0init k1amp k2cps = opcode "randi" args
  where args = [to k1amp, to k2cps] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31A' :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Arate
rnd31A' i0init k1scl k2rpow = opcode "rnd31" args
  where args = [to k1scl, to k2rpow] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31A :: (K k0, K k1) => [Irate] -> k0 -> k1 -> SideEffect Arate
rnd31A i0init k1scl k2rpow = opcode "rnd31" args
  where args = [to k1scl, to k2rpow] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31I' :: [Irate] -> Irate -> Irate -> Irate
rnd31I' i0init i1scl i2rpow = opcode "rnd31" args
  where args = [to i1scl, to i2rpow] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31I :: [Irate] -> Irate -> Irate -> SideEffect Irate
rnd31I i0init i1scl i2rpow = opcode "rnd31" args
  where args = [to i1scl, to i2rpow] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31K' :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Krate
rnd31K' i0init k1scl k2rpow = opcode "rnd31" args
  where args = [to k1scl, to k2rpow] ++ map to i0init


-- | * opcode : rnd31
--  
--  
-- * syntax : 
--  
--  >   ax rnd31 kscl, krpow [, iseed]
--  >   ix rnd31 iscl, irpow [, iseed]
--  >   kx rnd31 kscl, krpow [, iseed]
--  
--  
-- * description : 
--  
--  31-bit bipolar random opcodes with controllable distribution.
-- These units are portable, i.e. using the same seed value will
-- generate the same random sequence on all systems. The
-- distribution of generated random numbers can be varied at k-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/rnd31.html>
 
rnd31K :: (K k0, K k1) => [Irate] -> k0 -> k1 -> SideEffect Krate
rnd31K i0init k1scl k2rpow = opcode "rnd31" args
  where args = [to k1scl, to k2rpow] ++ map to i0init


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomA' :: (K k0, K k1) => k0 -> k1 -> Arate
randomA' k0min k1max = opcode "random" args
  where args = [to k0min, to k1max]


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomA :: (K k0, K k1) => k0 -> k1 -> SideEffect Arate
randomA k0min k1max = opcode "random" args
  where args = [to k0min, to k1max]


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomI' :: Irate -> Irate -> Irate
randomI' i0min i1max = opcode "random" args
  where args = [to i0min, to i1max]


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomI :: Irate -> Irate -> SideEffect Irate
randomI i0min i1max = opcode "random" args
  where args = [to i0min, to i1max]


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomK' :: (K k0, K k1) => k0 -> k1 -> Krate
randomK' k0min k1max = opcode "random" args
  where args = [to k0min, to k1max]


-- | * opcode : random
--  
--  
-- * syntax : 
--  
--  >   ares random kmin, kmax
--  >   ires random imin, imax
--  >   kres random kmin, kmax
--  
--  
-- * description : 
--  
--  Generates is a controlled pseudo-random number series between
-- min and max values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/random.html>
 
randomK :: (K k0, K k1) => k0 -> k1 -> SideEffect Krate
randomK k0min k1max = opcode "random" args
  where args = [to k0min, to k1max]


-- | * opcode : randomh
--  
--  
-- * syntax : 
--  
--  >   ares randomh kmin, kmax, acps
--  >   kres randomh kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates random numbers with a user-defined limit and holds
-- them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomh.html>
 
randomhA' :: (K k0, K k1) => k0 -> k1 -> Arate -> Arate
randomhA' k0min k1max a2cps = opcode "randomh" args
  where args = [to k0min, to k1max, to a2cps]


-- | * opcode : randomh
--  
--  
-- * syntax : 
--  
--  >   ares randomh kmin, kmax, acps
--  >   kres randomh kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates random numbers with a user-defined limit and holds
-- them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomh.html>
 
randomhA :: (K k0, K k1) => k0 -> k1 -> Arate -> SideEffect Arate
randomhA k0min k1max a2cps = opcode "randomh" args
  where args = [to k0min, to k1max, to a2cps]


-- | * opcode : randomh
--  
--  
-- * syntax : 
--  
--  >   ares randomh kmin, kmax, acps
--  >   kres randomh kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates random numbers with a user-defined limit and holds
-- them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomh.html>
 
randomhK' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Krate
randomhK' k0min k1max k2cps = opcode "randomh" args
  where args = [to k0min, to k1max, to k2cps]


-- | * opcode : randomh
--  
--  
-- * syntax : 
--  
--  >   ares randomh kmin, kmax, acps
--  >   kres randomh kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates random numbers with a user-defined limit and holds
-- them for a period of time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomh.html>
 
randomhK ::
           (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Krate
randomhK k0min k1max k2cps = opcode "randomh" args
  where args = [to k0min, to k1max, to k2cps]


-- | * opcode : randomi
--  
--  
-- * syntax : 
--  
--  >   ares randomi kmin, kmax, acps
--  >   kres randomi kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates a user-controlled random number series with
-- interpolation between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomi.html>
 
randomiA' :: (K k0, K k1) => k0 -> k1 -> Arate -> Arate
randomiA' k0min k1max a2cps = opcode "randomi" args
  where args = [to k0min, to k1max, to a2cps]


-- | * opcode : randomi
--  
--  
-- * syntax : 
--  
--  >   ares randomi kmin, kmax, acps
--  >   kres randomi kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates a user-controlled random number series with
-- interpolation between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomi.html>
 
randomiA :: (K k0, K k1) => k0 -> k1 -> Arate -> SideEffect Arate
randomiA k0min k1max a2cps = opcode "randomi" args
  where args = [to k0min, to k1max, to a2cps]


-- | * opcode : randomi
--  
--  
-- * syntax : 
--  
--  >   ares randomi kmin, kmax, acps
--  >   kres randomi kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates a user-controlled random number series with
-- interpolation between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomi.html>
 
randomiK' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Krate
randomiK' k0min k1max k2cps = opcode "randomi" args
  where args = [to k0min, to k1max, to k2cps]


-- | * opcode : randomi
--  
--  
-- * syntax : 
--  
--  >   ares randomi kmin, kmax, acps
--  >   kres randomi kmin, kmax, kcps
--  
--  
-- * description : 
--  
--  Generates a user-controlled random number series with
-- interpolation between each new number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/randomi.html>
 
randomiK ::
           (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Krate
randomiK k0min k1max k2cps = opcode "randomi" args
  where args = [to k0min, to k1max, to k2cps]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandA' :: (K k0) => k0 -> Arate
trirandA' k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandA :: (K k0) => k0 -> SideEffect Arate
trirandA k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandI' :: (K k0) => k0 -> Irate
trirandI' k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandI :: (K k0) => k0 -> SideEffect Irate
trirandI k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandK' :: (K k0) => k0 -> Krate
trirandK' k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : trirand
--  
--  
-- * syntax : 
--  
--  >   ares trirand krange
--  >   ires trirand krange
--  >   kres trirand krange
--  
--  
-- * description : 
--  
--  Triangular distribution random number generator. This is an
-- x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trirand.html>
 
trirandK :: (K k0) => k0 -> SideEffect Krate
trirandK k0range = opcode "trirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandA' :: (K k0) => k0 -> Arate
unirandA' k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandA :: (K k0) => k0 -> SideEffect Arate
unirandA k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandI' :: (K k0) => k0 -> Irate
unirandI' k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandI :: (K k0) => k0 -> SideEffect Irate
unirandI k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandK' :: (K k0) => k0 -> Krate
unirandK' k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : unirand
--  
--  
-- * syntax : 
--  
--  >   ares unirand krange
--  >   ires unirand krange
--  >   kres unirand krange
--  
--  
-- * description : 
--  
--  Uniform distribution random number generator (positive values
-- only). This is an x-class noise generator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/unirand.html>
 
unirandK :: (K k0) => k0 -> SideEffect Krate
unirandK k0range = opcode "unirand" args
  where args = [to k0range]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdA' :: (X x0) => x0 -> x0
urdA' x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdA :: (X x0) => x0 -> x0
urdA x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdI' :: (X x0) => x0 -> x0
urdI' x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdI :: (X x0) => x0 -> x0
urdI x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdK' :: (X x0) => x0 -> x0
urdK' x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : urd
--  
--  
-- * syntax : 
--  
--  >   aout = urd(ktableNum)
--  >   iout = urd(itableNum)
--  >   kout = urd(ktableNum)
--  
--  
-- * description : 
--  
--  A discrete user-defined-distribution random generator that can
-- be used as a function.
--  
--  
-- * url : <http://www.csounds.com/manual/html/urd.html>
 
urdK :: (X x0) => x0 -> x0
urdK x0sig = prefixOperation "urd" args
  where args = [to x0sig]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullA' :: (K k0, K k1) => k0 -> k1 -> Arate
weibullA' k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullA :: (K k0, K k1) => k0 -> k1 -> SideEffect Arate
weibullA k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullI' :: (K k0, K k1) => k0 -> k1 -> Irate
weibullI' k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullI :: (K k0, K k1) => k0 -> k1 -> SideEffect Irate
weibullI k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullK' :: (K k0, K k1) => k0 -> k1 -> Krate
weibullK' k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : weibull
--  
--  
-- * syntax : 
--  
--  >   ares weibull ksigma, ktau
--  >   ires weibull ksigma, ktau
--  >   kres weibull ksigma, ktau
--  
--  
-- * description : 
--  
--  Weibull distribution random number generator (positive values
-- only). This is an x-class noise generator
--  
--  
-- * url : <http://www.csounds.com/manual/html/weibull.html>
 
weibullK :: (K k0, K k1) => k0 -> k1 -> SideEffect Krate
weibullK k0sigma k1tau = opcode "weibull" args
  where args = [to k0sigma, to k1tau]


-- | * opcode : jitter
--  
--  
-- * syntax : 
--  
--  >   kout jitter kamp, kcpsMin, kcpsMax
--  
--  
-- * description : 
--  
--  Generates a segmented line whose segments are randomly
-- generated.
--  
--  
-- * url : <http://www.csounds.com/manual/html/jitter.html>
 
jitter' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Krate
jitter' k0amp k1cpsMin k2cpsMax = opcode "jitter" args
  where args = [to k0amp, to k1cpsMin, to k2cpsMax]


-- | * opcode : jitter
--  
--  
-- * syntax : 
--  
--  >   kout jitter kamp, kcpsMin, kcpsMax
--  
--  
-- * description : 
--  
--  Generates a segmented line whose segments are randomly
-- generated.
--  
--  
-- * url : <http://www.csounds.com/manual/html/jitter.html>
 
jitter :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Krate
jitter k0amp k1cpsMin k2cpsMax = opcode "jitter" args
  where args = [to k0amp, to k1cpsMin, to k2cpsMax]


-- | * opcode : jitter2
--  
--  
-- * syntax : 
--  
--  >   kout jitter2 ktotamp, kamp1, kcps1, kamp2, kcps2, kamp3, kcps3
--  
--  
-- * description : 
--  
--  Generates a segmented line with user-controllable random
-- segments.
--  
--  
-- * url : <http://www.csounds.com/manual/html/jitter2.html>
 
jitter2' ::
           (K k0, K k1, K k2, K k3, K k4, K k5, K k6) =>
           k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> Krate
jitter2' k0totamp k1amp1 k2cps1 k3amp2 k4cps2 k5amp3 k6cps3
  = opcode "jitter2" args
  where args
          = [to k0totamp, to k1amp1, to k2cps1, to k3amp2, to k4cps2,
             to k5amp3, to k6cps3]


-- | * opcode : jitter2
--  
--  
-- * syntax : 
--  
--  >   kout jitter2 ktotamp, kamp1, kcps1, kamp2, kcps2, kamp3, kcps3
--  
--  
-- * description : 
--  
--  Generates a segmented line with user-controllable random
-- segments.
--  
--  
-- * url : <http://www.csounds.com/manual/html/jitter2.html>
 
jitter2 ::
          (K k0, K k1, K k2, K k3, K k4, K k5, K k6) =>
          k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> SideEffect Krate
jitter2 k0totamp k1amp1 k2cps1 k3amp2 k4cps2 k5amp3 k6cps3
  = opcode "jitter2" args
  where args
          = [to k0totamp, to k1amp1, to k2cps1, to k3amp2, to k4cps2,
             to k5amp3, to k6cps3]


-- | * opcode : trandom
--  
--  
-- * syntax : 
--  
--  >   kout trandom ktrig, kmin, kmax
--  
--  
-- * description : 
--  
--  Generates a controlled pseudo-random number series between min
-- and max values at k-rate whenever the trigger parameter is
-- different to 0.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trandom.html>
 
trandom' :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> Krate
trandom' k0trig k1min k2max = opcode "trandom" args
  where args = [to k0trig, to k1min, to k2max]


-- | * opcode : trandom
--  
--  
-- * syntax : 
--  
--  >   kout trandom ktrig, kmin, kmax
--  
--  
-- * description : 
--  
--  Generates a controlled pseudo-random number series between min
-- and max values at k-rate whenever the trigger parameter is
-- different to 0.
--  
--  
-- * url : <http://www.csounds.com/manual/html/trandom.html>
 
trandom :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> SideEffect Krate
trandom k0trig k1min k2max = opcode "trandom" args
  where args = [to k0trig, to k1min, to k2max]