-- | Basic Oscillators
module CsoundExpr.Opcodes.Siggen.Basic
    (oscbnk,
     oscilA,
     oscilK,
     oscil3A,
     oscil3K,
     osciliA,
     osciliK,
     oscils,
     poscilAAA,
     poscilAAK,
     poscilAKA,
     poscilAKK,
     poscilI,
     poscilK,
     poscil3A,
     poscil3K,
     osciliktA,
     osciliktK,
     osciliktp,
     oscilikts,
     osciln,
     lfoA,
     lfoK,
     vibr,
     vibrato)
where



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



-- | * opcode : oscbnk
--  
--  
-- * syntax : 
--  
--  >   ares oscbnk kcps, kamd, kfmd, kpmd, iovrlap, iseed, kl1minf, kl1maxf, 
--  >       kl2minf, kl2maxf, ilfomode, keqminf, keqmaxf, keqminl, keqmaxl, 
--  >       keqminq, keqmaxq, ieqmode, kfn [, il1fn] [, il2fn] [, ieqffn] 
--  >       [, ieqlfn] [, ieqqfn] [, itabl] [, ioutfn]
--  
--  
-- * description : 
--  
--  This unit generator mixes the output of any number of
-- oscillators. The frequency, phase, and amplitude of each
-- oscillator can be modulated by two LFOs (all oscillators have a
-- separate set of LFOs, with different phase and frequency);
-- additionally, the output of each oscillator can be filtered
-- through an optional parametric equalizer (also controlled by the
-- LFOs). This opcode is most useful for rendering ensemble
-- (strings, choir, etc.) instruments.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscbnk.html>
 
oscbnk ::
         (K k0, K k1, K k2, K k3, K k4, K k5, K k6, K k7, K k8, K k9, K k10,
          K k11, K k12, K k13, K k14) =>
         [Irate] ->
           k0 ->
             k1 ->
               k2 ->
                 k3 ->
                   Irate ->
                     Irate ->
                       k4 ->
                         k5 ->
                           k6 ->
                             k7 ->
                               Irate ->
                                 k8 -> k9 -> k10 -> k11 -> k12 -> k13 -> Irate -> k14 -> Arate
oscbnk i0init k1cps k2amd k3fmd k4pmd i5ovrlap i6seed k7l1minf
  k8l1maxf k9l2minf k10l2maxf i11lfomode k12eqminf k13eqmaxf
  k14eqminl k15eqmaxl k16eqminq k17eqmaxq i18eqmode k19fn
  = opcode "oscbnk" args
  where args
          = [to k1cps, to k2amd, to k3fmd, to k4pmd, to i5ovrlap, to i6seed,
             to k7l1minf, to k8l1maxf, to k9l2minf, to k10l2maxf, to i11lfomode,
             to k12eqminf, to k13eqmaxf, to k14eqminl, to k15eqmaxl,
             to k16eqminq, to k17eqmaxq, to i18eqmode, to k19fn]
              ++ map to i0init


-- | * opcode : oscil
--  
--  
-- * syntax : 
--  
--  >   ares oscil xamp, xcps, ifn [, iphs]
--  >   kres oscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscil reads table ifn sequentially and repeatedly at a frequency
-- xcps. The amplitude is scaled by xamp.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscil.html>
 
oscilA :: (X x0, X x1) => [Irate] -> x0 -> x1 -> Irate -> Arate
oscilA i0init x1amp x2cps i3fn = opcode "oscil" args
  where args = [to x1amp, to x2cps, to i3fn] ++ map to i0init


-- | * opcode : oscil
--  
--  
-- * syntax : 
--  
--  >   ares oscil xamp, xcps, ifn [, iphs]
--  >   kres oscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscil reads table ifn sequentially and repeatedly at a frequency
-- xcps. The amplitude is scaled by xamp.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscil.html>
 
oscilK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Krate
oscilK i0init k1amp k2cps i3fn = opcode "oscil" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : oscil3
--  
--  
-- * syntax : 
--  
--  >   ares oscil3 xamp, xcps, ifn [, iphs]
--  >   kres oscil3 kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscil3 reads table ifn sequentially and repeatedly at a
-- frequency xcps. The amplitude is scaled by xamp. Cubic
-- interpolation is applied for table look up from internal phase
-- values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscil3.html>
 
oscil3A :: (X x0, X x1) => [Irate] -> x0 -> x1 -> Irate -> Arate
oscil3A i0init x1amp x2cps i3fn = opcode "oscil3" args
  where args = [to x1amp, to x2cps, to i3fn] ++ map to i0init


-- | * opcode : oscil3
--  
--  
-- * syntax : 
--  
--  >   ares oscil3 xamp, xcps, ifn [, iphs]
--  >   kres oscil3 kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscil3 reads table ifn sequentially and repeatedly at a
-- frequency xcps. The amplitude is scaled by xamp. Cubic
-- interpolation is applied for table look up from internal phase
-- values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscil3.html>
 
oscil3K :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Krate
oscil3K i0init k1amp k2cps i3fn = opcode "oscil3" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : oscili
--  
--  
-- * syntax : 
--  
--  >   ares oscili xamp, xcps, ifn [, iphs]
--  >   kres oscili kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscili reads table ifn sequentially and repeatedly at a
-- frequency xcps. The amplitude is scaled by xamp. Linear
-- interpolation is applied for table look up from internal phase
-- values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscili.html>
 
osciliA :: (X x0, X x1) => [Irate] -> x0 -> x1 -> Irate -> Arate
osciliA i0init x1amp x2cps i3fn = opcode "oscili" args
  where args = [to x1amp, to x2cps, to i3fn] ++ map to i0init


-- | * opcode : oscili
--  
--  
-- * syntax : 
--  
--  >   ares oscili xamp, xcps, ifn [, iphs]
--  >   kres oscili kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  oscili reads table ifn sequentially and repeatedly at a
-- frequency xcps. The amplitude is scaled by xamp. Linear
-- interpolation is applied for table look up from internal phase
-- values.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscili.html>
 
osciliK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Krate
osciliK i0init k1amp k2cps i3fn = opcode "oscili" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : oscils
--  
--  
-- * syntax : 
--  
--  >   ares oscils iamp, icps, iphs [, iflg]
--  
--  
-- * description : 
--  
--  Simple, fast sine oscillator, that uses only one multiply, and
-- two add operations to generate one sample of output, and does not
-- require a function table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscils.html>
 
oscils :: [Irate] -> Irate -> Irate -> Irate -> Arate
oscils i0init i1amp i2cps i3phs = opcode "oscils" args
  where args = [to i1amp, to i2cps, to i3phs] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilAAA :: [Irate] -> Arate -> Arate -> Irate -> Arate
poscilAAA i0init a1amp a2cps i3fn = opcode "poscil" args
  where args = [to a1amp, to a2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilAAK :: (K k0) => [Irate] -> Arate -> k0 -> Irate -> Arate
poscilAAK i0init a1amp k2cps i3fn = opcode "poscil" args
  where args = [to a1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilAKA :: (K k0) => [Irate] -> k0 -> Arate -> Irate -> Arate
poscilAKA i0init k1amp a2cps i3fn = opcode "poscil" args
  where args = [to k1amp, to a2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilAKK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Arate
poscilAKK i0init k1amp k2cps i3fn = opcode "poscil" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilI :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Irate
poscilI i0init k1amp k2cps i3fn = opcode "poscil" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil
--  
--  
-- * syntax : 
--  
--  >   ares poscil aamp, acps, ifn [, iphs]
--  >   ares poscil aamp, kcps, ifn [, iphs]
--  >   ares poscil kamp, acps, ifn [, iphs]
--  >   ares poscil kamp, kcps, ifn [, iphs]
--  >   ires poscil kamp, kcps, ifn [, iphs]
--  >   kres poscil kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil.html>
 
poscilK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Krate
poscilK i0init k1amp k2cps i3fn = opcode "poscil" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil3
--  
--  
-- * syntax : 
--  
--  >   ares poscil3 kamp, kcps, ifn [, iphs]
--  >   kres poscil3 kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator with cubic interpolation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil3.html>
 
poscil3A :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Arate
poscil3A i0init k1amp k2cps i3fn = opcode "poscil3" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : poscil3
--  
--  
-- * syntax : 
--  
--  >   ares poscil3 kamp, kcps, ifn [, iphs]
--  >   kres poscil3 kamp, kcps, ifn [, iphs]
--  
--  
-- * description : 
--  
--  High precision oscillator with cubic interpolation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/poscil3.html>
 
poscil3K :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Krate
poscil3K i0init k1amp k2cps i3fn = opcode "poscil3" args
  where args = [to k1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : oscilikt
--  
--  
-- * syntax : 
--  
--  >   ares oscilikt xamp, xcps, kfn [, iphs] [, istor]
--  >   kres oscilikt kamp, kcps, kfn [, iphs] [, istor]
--  
--  
-- * description : 
--  
--  oscilikt is very similar to oscili, but allows changing the
-- table number at k-rate. It is slightly slower than oscili
-- (especially with high control rate), although also more accurate
-- as it uses a 31-bit phase accumulator, as opposed to the 24-bit
-- one used by oscili.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscilikt.html>
 
osciliktA ::
            (X x0, X x1, K k0) => [Irate] -> x0 -> x1 -> k0 -> Arate
osciliktA i0init x1amp x2cps k3fn = opcode "oscilikt" args
  where args = [to x1amp, to x2cps, to k3fn] ++ map to i0init


-- | * opcode : oscilikt
--  
--  
-- * syntax : 
--  
--  >   ares oscilikt xamp, xcps, kfn [, iphs] [, istor]
--  >   kres oscilikt kamp, kcps, kfn [, iphs] [, istor]
--  
--  
-- * description : 
--  
--  oscilikt is very similar to oscili, but allows changing the
-- table number at k-rate. It is slightly slower than oscili
-- (especially with high control rate), although also more accurate
-- as it uses a 31-bit phase accumulator, as opposed to the 24-bit
-- one used by oscili.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscilikt.html>
 
osciliktK ::
            (K k0, K k1, K k2) => [Irate] -> k0 -> k1 -> k2 -> Krate
osciliktK i0init k1amp k2cps k3fn = opcode "oscilikt" args
  where args = [to k1amp, to k2cps, to k3fn] ++ map to i0init


-- | * opcode : osciliktp
--  
--  
-- * syntax : 
--  
--  >   ares osciliktp kcps, kfn, kphs [, istor]
--  
--  
-- * description : 
--  
--  osciliktp allows phase modulation (which is actually implemented
-- as k-rate frequency modulation, by differentiating phase input).
-- The disadvantage is that there is no amplitude control, and
-- frequency can be varied only at the control-rate. This opcode can
-- be faster or slower than oscilikt, depending on the control-rate.
--  
--  
-- * url : <http://www.csounds.com/manual/html/osciliktp.html>
 
osciliktp ::
            (K k0, K k1, K k2) => [Irate] -> k0 -> k1 -> k2 -> Arate
osciliktp i0init k1cps k2fn k3phs = opcode "osciliktp" args
  where args = [to k1cps, to k2fn, to k3phs] ++ map to i0init


-- | * opcode : oscilikts
--  
--  
-- * syntax : 
--  
--  >   ares oscilikts xamp, xcps, kfn, async, kphs [, istor]
--  
--  
-- * description : 
--  
--  oscilikts is the same as oscilikt. Except it has a sync input
-- that can be used to re-initialize the oscillator to a k-rate
-- phase value. It is slower than oscilikt and osciliktp.
--  
--  
-- * url : <http://www.csounds.com/manual/html/oscilikts.html>
 
oscilikts ::
            (X x0, X x1, K k0, K k1) =>
            [Irate] -> x0 -> x1 -> k0 -> Arate -> k1 -> Arate
oscilikts i0init x1amp x2cps k3fn a4sync k5phs
  = opcode "oscilikts" args
  where args
          = [to x1amp, to x2cps, to k3fn, to a4sync, to k5phs] ++
              map to i0init


-- | * opcode : osciln
--  
--  
-- * syntax : 
--  
--  >   ares osciln kamp, ifrq, ifn, itimes
--  
--  
-- * description : 
--  
--  Accesses table values at a user-defined frequency. This opcode
-- can also be written as oscilx.
--  
--  
-- * url : <http://www.csounds.com/manual/html/osciln.html>
 
osciln :: (K k0) => k0 -> Irate -> Irate -> Irate -> Arate
osciln k0amp i1frq i2fn i3times = opcode "osciln" args
  where args = [to k0amp, to i1frq, to i2fn, to i3times]


-- | * opcode : lfo
--  
--  
-- * syntax : 
--  
--  >   kres lfo kamp, kcps [, itype]
--  >   ares lfo kamp, kcps [, itype]
--  
--  
-- * description : 
--  
--  A low frequency oscillator of various shapes.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lfo.html>
 
lfoA :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Arate
lfoA i0init k1amp k2cps = opcode "lfo" args
  where args = [to k1amp, to k2cps] ++ map to i0init


-- | * opcode : lfo
--  
--  
-- * syntax : 
--  
--  >   kres lfo kamp, kcps [, itype]
--  >   ares lfo kamp, kcps [, itype]
--  
--  
-- * description : 
--  
--  A low frequency oscillator of various shapes.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lfo.html>
 
lfoK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Krate
lfoK i0init k1amp k2cps = opcode "lfo" args
  where args = [to k1amp, to k2cps] ++ map to i0init


-- | * opcode : vibr
--  
--  
-- * syntax : 
--  
--  >   kout vibr kAverageAmp, kAverageFreq, ifn
--  
--  
-- * description : 
--  
--  Easier-to-use user-controllable vibrato.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vibr.html>
 
vibr :: (K k0, K k1) => k0 -> k1 -> Irate -> Krate
vibr k0AverageAmp k1AverageFreq i2fn = opcode "vibr" args
  where args = [to k0AverageAmp, to k1AverageFreq, to i2fn]


-- | * opcode : vibrato
--  
--  
-- * syntax : 
--  
--  >   kout vibrato kAverageAmp, kAverageFreq, kRandAmountAmp, 
--  >       kRandAmountFreq, kAmpMinRate, kAmpMaxRate, kcpsMinRate, 
--  >       kcpsMaxRate, ifn [, iphs]
--  
--  
-- * description : 
--  
--  Generates a natural-sounding user-controllable vibrato.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vibrato.html>
 
vibrato ::
          (K k0, K k1, K k2, K k3, K k4, K k5, K k6, K k7) =>
          [Irate] ->
            k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> k7 -> Irate -> Krate
vibrato i0init k1AverageAmp k2AverageFreq k3RandAmountAmp
  k4RandAmountFreq k5AmpMinRate k6AmpMaxRate k7cpsMinRate
  k8cpsMaxRate i9fn = opcode "vibrato" args
  where args
          = [to k1AverageAmp, to k2AverageFreq, to k3RandAmountAmp,
             to k4RandAmountFreq, to k5AmpMinRate, to k6AmpMaxRate,
             to k7cpsMinRate, to k8cpsMaxRate, to i9fn]
              ++ map to i0init