-- | Granular Synthesis
module CsoundExpr.Opcodes.Siggen.Granular
    (diskgrain,
     fof,
     fof2,
     fog,
     grain,
     grain2,
     grain3,
     granule,
     partikkel,
     partikkelsync,
     sndwarp,
     sndwarpst,
     syncgrain,
     syncloop,
     vosim)
where



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



-- | * opcode : diskgrain
--  
--  
-- * syntax : 
--  
--  >   asig diskgrain Sfname, kamp, kfreq, kpitch, kgrsize, kprate, 
--  >       ifun, iolaps [,imaxgrsize, ioffset]
--  
--  
-- * description : 
--  
--  diskgrain implements synchronous granular synthesis. The source
-- sound for the grains is obtained by reading a soundfile
-- containing the samples of the source waveform.
--  
--  
-- * url : <http://www.csounds.com/manual/html/diskgrain.html>
 
diskgrain ::
            (K k0, K k1, K k2, K k3, K k4) =>
            [Irate] ->
              String -> k0 -> k1 -> k2 -> k3 -> k4 -> Irate -> Irate -> Arate
diskgrain i0init s1fname k2amp k3freq k4pitch k5grsize k6prate
  i7fun i8olaps = opcode "diskgrain" args
  where args
          = [to s1fname, to k2amp, to k3freq, to k4pitch, to k5grsize,
             to k6prate, to i7fun, to i8olaps]
              ++ map to i0init


-- | * opcode : fof
--  
--  
-- * syntax : 
--  
--  >   ares fof xamp, xfund, xform, koct, kband, kris, kdur, kdec, iolaps, 
--  >       ifna, ifnb, itotdur [, iphs] [, ifmode] [, iskip]
--  
--  
-- * description : 
--  
--  Audio output is a succession of sinusoid bursts initiated at
-- frequency xfund with a spectral peak at xform. For xfund above 25
-- Hz these bursts produce a speech-like formant with spectral
-- characteristics determined by the k-input parameters. For lower
-- fundamentals this generator provides a special form of granular
-- synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fof.html>
 
fof ::
      (X x0, X x1, X x2, K k0, K k1, K k2, K k3, K k4) =>
      [Irate] ->
        x0 ->
          x1 ->
            x2 ->
              k0 ->
                k1 -> k2 -> k3 -> k4 -> Irate -> Irate -> Irate -> Irate -> Arate
fof i0init x1amp x2fund x3form k4oct k5band k6ris k7dur k8dec
  i9olaps i10fna i11fnb i12totdur = opcode "fof" args
  where args
          = [to x1amp, to x2fund, to x3form, to k4oct, to k5band, to k6ris,
             to k7dur, to k8dec, to i9olaps, to i10fna, to i11fnb, to i12totdur]
              ++ map to i0init


-- | * opcode : fof2
--  
--  
-- * syntax : 
--  
--  >   ares fof2 xamp, xfund, xform, koct, kband, kris, kdur, kdec, iolaps, 
--  >       ifna, ifnb, itotdur, kphs, kgliss [, iskip]
--  
--  
-- * description : 
--  
--  Audio output is a succession of sinusoid bursts initiated at
-- frequency xfund with a spectral peak at xform. For xfund above 25
-- Hz these bursts produce a speech-like formant with spectral
-- characteristics determined by the k-input parameters. For lower
-- fundamentals this generator provides a special form of granular
-- synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fof2.html>
 
fof2 ::
       (X x0, X x1, X x2, K k0, K k1, K k2, K k3, K k4, K k5, K k6) =>
       [Irate] ->
         x0 ->
           x1 ->
             x2 ->
               k0 ->
                 k1 ->
                   k2 ->
                     k3 -> k4 -> Irate -> Irate -> Irate -> Irate -> k5 -> k6 -> Arate
fof2 i0init x1amp x2fund x3form k4oct k5band k6ris k7dur k8dec
  i9olaps i10fna i11fnb i12totdur k13phs k14gliss
  = opcode "fof2" args
  where args
          = [to x1amp, to x2fund, to x3form, to k4oct, to k5band, to k6ris,
             to k7dur, to k8dec, to i9olaps, to i10fna, to i11fnb, to i12totdur,
             to k13phs, to k14gliss]
              ++ map to i0init


-- | * opcode : fog
--  
--  
-- * syntax : 
--  
--  >   ares fog xamp, xdens, xtrans, aspd, koct, kband, kris, kdur, kdec, 
--  >       iolaps, ifna, ifnb, itotdur [, iphs] [, itmode] [, iskip]
--  
--  
-- * description : 
--  
--  Audio output is a succession of grains derived from data in a
-- stored function table ifna. The local envelope of these grains
-- and their timing is based on the model of fof synthesis and
-- permits detailed control of the granular synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fog.html>
 
fog ::
      (X x0, X x1, X x2, K k0, K k1, K k2, K k3, K k4) =>
      [Irate] ->
        x0 ->
          x1 ->
            x2 ->
              Arate ->
                k0 ->
                  k1 -> k2 -> k3 -> k4 -> Irate -> Irate -> Irate -> Irate -> Arate
fog i0init x1amp x2dens x3trans a4spd k5oct k6band k7ris k8dur
  k9dec i10olaps i11fna i12fnb i13totdur = opcode "fog" args
  where args
          = [to x1amp, to x2dens, to x3trans, to a4spd, to k5oct, to k6band,
             to k7ris, to k8dur, to k9dec, to i10olaps, to i11fna, to i12fnb,
             to i13totdur]
              ++ map to i0init


-- | * opcode : grain
--  
--  
-- * syntax : 
--  
--  >   ares grain xamp, xpitch, xdens, kampoff, kpitchoff, kgdur, igfn, 
--  >       iwfn, imgdur [, igrnd]
--  
--  
-- * description : 
--  
--  Generates granular synthesis textures.
--  
--  
-- * url : <http://www.csounds.com/manual/html/grain.html>
 
grain ::
        (X x0, X x1, X x2, K k0, K k1, K k2) =>
        [Irate] ->
          x0 ->
            x1 -> x2 -> k0 -> k1 -> k2 -> Irate -> Irate -> Irate -> Arate
grain i0init x1amp x2pitch x3dens k4ampoff k5pitchoff k6gdur i7gfn
  i8wfn i9mgdur = opcode "grain" args
  where args
          = [to x1amp, to x2pitch, to x3dens, to k4ampoff, to k5pitchoff,
             to k6gdur, to i7gfn, to i8wfn, to i9mgdur]
              ++ map to i0init


-- | * opcode : grain2
--  
--  
-- * syntax : 
--  
--  >   ares grain2 kcps, kfmd, kgdur, iovrlp, kfn, iwfn [, irpow] 
--  >       [, iseed] [, imode]
--  
--  
-- * description : 
--  
--  Generate granular synthesis textures. grain2 is simpler to use,
-- but grain3 offers more control.
--  
--  
-- * url : <http://www.csounds.com/manual/html/grain2.html>
 
grain2 ::
         (K k0, K k1, K k2, K k3) =>
         [Irate] -> k0 -> k1 -> k2 -> Irate -> k3 -> Irate -> Arate
grain2 i0init k1cps k2fmd k3gdur i4ovrlp k5fn i6wfn
  = opcode "grain2" args
  where args
          = [to k1cps, to k2fmd, to k3gdur, to i4ovrlp, to k5fn, to i6wfn] ++
              map to i0init


-- | * opcode : grain3
--  
--  
-- * syntax : 
--  
--  >   ares grain3 kcps, kphs, kfmd, kpmd, kgdur, kdens, imaxovr, kfn, iwfn, 
--  >       kfrpow, kprpow [, iseed] [, imode]
--  
--  
-- * description : 
--  
--  Generate granular synthesis textures. grain2 is simpler to use
-- but grain3 offers more control.
--  
--  
-- * url : <http://www.csounds.com/manual/html/grain3.html>
 
grain3 ::
         (K k0, K k1, K k2, K k3, K k4, K k5, K k6, K k7, K k8) =>
         [Irate] ->
           k0 ->
             k1 ->
               k2 -> k3 -> k4 -> k5 -> Irate -> k6 -> Irate -> k7 -> k8 -> Arate
grain3 i0init k1cps k2phs k3fmd k4pmd k5gdur k6dens i7maxovr k8fn
  i9wfn k10frpow k11prpow = opcode "grain3" args
  where args
          = [to k1cps, to k2phs, to k3fmd, to k4pmd, to k5gdur, to k6dens,
             to i7maxovr, to k8fn, to i9wfn, to k10frpow, to k11prpow]
              ++ map to i0init


-- | * opcode : granule
--  
--  
-- * syntax : 
--  
--  >   ares granule xamp, ivoice, iratio, imode, ithd, ifn, ipshift, igskip, 
--  >       igskip_os, ilength, kgap, igap_os, kgsize, igsize_os, iatt, idec 
--  >       [, iseed] [, ipitch1] [, ipitch2] [, ipitch3] [, ipitch4] [, ifnenv]
--  
--  
-- * description : 
--  
--  The granule unit generator is more complex than grain, but does
-- add new possibilities.
--  
--  
-- * url : <http://www.csounds.com/manual/html/granule.html>
 
granule ::
          (X x0, K k0, K k1) =>
          [Irate] ->
            x0 ->
              Irate ->
                Irate ->
                  Irate ->
                    Irate ->
                      Irate ->
                        Irate ->
                          Irate ->
                            Irate ->
                              Irate -> k0 -> Irate -> k1 -> Irate -> Irate -> Irate -> Arate
granule i0init x1amp i2voice i3ratio i4mode i5thd i6fn i7pshift
  i8gskip i9gskip_os i10length k11gap i12gap_os k13gsize i14gsize_os
  i15att i16dec = opcode "granule" args
  where args
          = [to x1amp, to i2voice, to i3ratio, to i4mode, to i5thd, to i6fn,
             to i7pshift, to i8gskip, to i9gskip_os, to i10length, to k11gap,
             to i12gap_os, to k13gsize, to i14gsize_os, to i15att, to i16dec]
              ++ map to i0init


-- | * opcode : partikkel
--  
--  
-- * syntax : 
--  
--  >   a1 [, a2, a3, a4, a5, a6, a7, a8] partikkel agrainfreq, 
--  >       kdistribution, idisttab, async, kenv2amt, ienv2tab, ienv_attack, 
--  >       ienv_decay, ksustain_amount, ka_d_ratio, kduration, kamp, igainmasks, 
--  >       kwavfreq, ksweepshape, iwavfreqstarttab, iwavfreqendtab, awavfm, 
--  >       ifmamptab, kfmenv, icosine, ktraincps, knumpartials, kchroma, 
--  >       ichannelmasks, krandommask, kwaveform1, kwaveform2, kwaveform3, 
--  >       kwaveform4, iwaveamptab, asamplepos1, asamplepos2, asamplepos3, 
--  >       asamplepos4, kwavekey1, kwavekey2, kwavekey3, kwavekey4, imax_grains 
--  >       [, iopcode_id]
--  
--  
-- * description : 
--  
--  partikkel was conceived after reading Curtis Roads' book
-- "Microsound", and the goal was to create an opcode that was
-- capable of all time-domain varieties of granular synthesis
-- described in this book. The idea being that most of the
-- techniques only differ in parameter values, and by having a
-- single opcode that can do all varieties of granular synthesis
-- makes it possible to interpolate between techniques. Granular
-- synthesis is sometimes dubbed particle synthesis, and it was
-- thought apt to name the opcode partikkel to distinguish it from
-- other granular opcodes.
--  
--  
-- * url : <http://www.csounds.com/manual/html/partikkel.html>
 
partikkel ::
            (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, K k15, K k16, K k17, K k18, K k19,
             K k20) =>
            [Irate] ->
              Arate ->
                k0 ->
                  Irate ->
                    Arate ->
                      k1 ->
                        Irate ->
                          Irate ->
                            Irate ->
                              k2 ->
                                k3 ->
                                  k4 ->
                                    k5 ->
                                      Irate ->
                                        k6 ->
                                          k7 ->
                                            Irate ->
                                              Irate ->
                                                Arate ->
                                                  Irate ->
                                                    k8 ->
                                                      Irate ->
                                                        k9 ->
                                                          k10 ->
                                                            k11 ->
                                                              Irate ->
                                                                k12 ->
                                                                  k13 ->
                                                                    k14 ->
                                                                      k15 ->
                                                                        k16 ->
                                                                          Irate ->
                                                                            Arate ->
                                                                              Arate ->
                                                                                Arate ->
                                                                                  Arate ->
                                                                                    k17 ->
                                                                                      k18 ->
                                                                                        k19 ->
                                                                                          k20 ->
                                                                                            Irate ->
                                                                                              MultiOut
partikkel i0init a1grainfreq k2distribution i3disttab a4sync
  k5env2amt i6env2tab i7env_attack i8env_decay k9sustain_amount
  k10a_d_ratio k11duration k12amp i13gainmasks k14wavfreq
  k15sweepshape i16wavfreqstarttab i17wavfreqendtab a18wavfm
  i19fmamptab k20fmenv i21cosine k22traincps k23numpartials k24chroma
  i25channelmasks k26randommask k27waveform1 k28waveform2
  k29waveform3 k30waveform4 i31waveamptab a32samplepos1 a33samplepos2
  a34samplepos3 a35samplepos4 k36wavekey1 k37wavekey2 k38wavekey3
  k39wavekey4 i40max_grains = opcode "partikkel" args
  where args
          = [to a1grainfreq, to k2distribution, to i3disttab, to a4sync,
             to k5env2amt, to i6env2tab, to i7env_attack, to i8env_decay,
             to k9sustain_amount, to k10a_d_ratio, to k11duration, to k12amp,
             to i13gainmasks, to k14wavfreq, to k15sweepshape,
             to i16wavfreqstarttab, to i17wavfreqendtab, to a18wavfm,
             to i19fmamptab, to k20fmenv, to i21cosine, to k22traincps,
             to k23numpartials, to k24chroma, to i25channelmasks,
             to k26randommask, to k27waveform1, to k28waveform2,
             to k29waveform3, to k30waveform4, to i31waveamptab,
             to a32samplepos1, to a33samplepos2, to a34samplepos3,
             to a35samplepos4, to k36wavekey1, to k37wavekey2, to k38wavekey3,
             to k39wavekey4, to i40max_grains]
              ++ map to i0init


-- | * opcode : partikkelsync
--  
--  
-- * syntax : 
--  
--  >   async [,aphase] partikkelsync iopcode_id
--  
--  
-- * description : 
--  
--  partikkelsync is an opcode for outputting partikkel's grain
-- scheduler clock pulse and phase. partikkelsync's output can be
-- used to synchronize other instances of the partikkel opcode to
-- the same clock.
--  
--  
-- * url : <http://www.csounds.com/manual/html/partikkelsync.html>
 
partikkelsync :: Irate -> MultiOut
partikkelsync i0opcode_id = opcode "partikkelsync" args
  where args = [to i0opcode_id]


-- | * opcode : sndwarp
--  
--  
-- * syntax : 
--  
--  >   ares [, ac] sndwarp xamp, xtimewarp, xresample, ifn1, ibeg, iwsize, 
--  >       irandw, ioverlap, ifn2, itimemode
--  
--  
-- * description : 
--  
--  sndwarp reads sound samples from a table and applies
-- time-stretching and/or pitch modification. Time and frequency
-- modification are independent from one another. For example, a
-- sound can be stretched in time while raising the pitch!
--  
--  
-- * url : <http://www.csounds.com/manual/html/sndwarp.html>
 
sndwarp ::
          (X x0, X x1, X x2) =>
          x0 ->
            x1 ->
              x2 ->
                Irate ->
                  Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
sndwarp x0amp x1timewarp x2resample i3fn1 i4beg i5wsize i6randw
  i7overlap i8fn2 i9timemode = opcode "sndwarp" args
  where args
          = [to x0amp, to x1timewarp, to x2resample, to i3fn1, to i4beg,
             to i5wsize, to i6randw, to i7overlap, to i8fn2, to i9timemode]


-- | * opcode : sndwarpst
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 [,ac1] [, ac2] sndwarpst xamp, xtimewarp, xresample, ifn1, 
--  >       ibeg, iwsize, irandw, ioverlap, ifn2, itimemode
--  
--  
-- * description : 
--  
--  sndwarpst reads stereo sound samples from a table and applies
-- time-stretching and/or pitch modification. Time and frequency
-- modification are independent from one another. For example, a
-- sound can be stretched in time while raising the pitch!
--  
--  
-- * url : <http://www.csounds.com/manual/html/sndwarpst.html>
 
sndwarpst ::
            (X x0, X x1, X x2) =>
            x0 ->
              x1 ->
                x2 ->
                  Irate ->
                    Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
sndwarpst x0amp x1timewarp x2resample i3fn1 i4beg i5wsize i6randw
  i7overlap i8fn2 i9timemode = opcode "sndwarpst" args
  where args
          = [to x0amp, to x1timewarp, to x2resample, to i3fn1, to i4beg,
             to i5wsize, to i6randw, to i7overlap, to i8fn2, to i9timemode]


-- | * opcode : syncgrain
--  
--  
-- * syntax : 
--  
--  >   asig syncgrain kamp, kfreq, kpitch, kgrsize, kprate, ifun1, 
--  >       ifun2, iolaps
--  
--  
-- * description : 
--  
--  syncgrain implements synchronous granular synthesis. The source
-- sound for the grains is obtained by reading a function table
-- containing the samples of the source waveform. For sampled-sound
-- sources, GEN01 is used. syncgrain will accept deferred allocation
-- tables.
--  
--  
-- * url : <http://www.csounds.com/manual/html/syncgrain.html>
 
syncgrain ::
            (K k0, K k1, K k2, K k3, K k4) =>
            k0 -> k1 -> k2 -> k3 -> k4 -> Irate -> Irate -> Irate -> Arate
syncgrain k0amp k1freq k2pitch k3grsize k4prate i5fun1 i6fun2
  i7olaps = opcode "syncgrain" args
  where args
          = [to k0amp, to k1freq, to k2pitch, to k3grsize, to k4prate,
             to i5fun1, to i6fun2, to i7olaps]


-- | * opcode : syncloop
--  
--  
-- * syntax : 
--  
--  >   asig syncloop kamp, kfreq, kpitch, kgrsize, kprate, klstart, 
--  >       klend, ifun1, ifun2, iolaps[,istart, iskip]
--  
--  
-- * description : 
--  
--  syncloop is a variation on syncgrain, which implements
-- synchronous granular synthesis. syncloop adds loop start and end
-- points and an optional start position. Loop start and end control
-- grain start positions, so the actual grains can go beyond the
-- loop points (if the loop points are not at the extremes of the
-- table), enabling seamless crossfading. For more information on
-- the granular synthesis process, check the syncgrain manual page.
--  
--  
-- * url : <http://www.csounds.com/manual/html/syncloop.html>
 
syncloop ::
           (K k0, K k1, K k2, K k3, K k4, K k5, K k6) =>
           [Irate] ->
             k0 ->
               k1 ->
                 k2 -> k3 -> k4 -> k5 -> k6 -> Irate -> Irate -> Irate -> Arate
syncloop i0init k1amp k2freq k3pitch k4grsize k5prate k6lstart
  k7lend i8fun1 i9fun2 i10olaps = opcode "syncloop" args
  where args
          = [to k1amp, to k2freq, to k3pitch, to k4grsize, to k5prate,
             to k6lstart, to k7lend, to i8fun1, to i9fun2, to i10olaps]
              ++ map to i0init


-- | * opcode : vosim
--  
--  
-- * syntax : 
--  
--  >   ar vosim kamp, kFund, kForm, kDecay, kPulseCount, kPulseFactor, ifn [, iskip]
--  
--  
-- * description : 
--  
--  This opcode produces a simple vocal simulation based on glottal
-- pulses with formant characteristics. Output is a series of sound
-- events, where each event is composed of a burst of squared sine
-- pulses followed by silence. The VOSIM (VOcal SIMulation)
-- synthesis method was developed by Kaegi and Tempelaars in the
-- 1970's.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vosim.html>
 
vosim ::
        (K k0, K k1, K k2, K k3, K k4, K k5) =>
        [Irate] -> k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> Irate -> Arate
vosim i0init k1amp k2Fund k3Form k4Decay k5PulseCount k6PulseFactor
  i7fn = opcode "vosim" args
  where args
          = [to k1amp, to k2Fund, to k3Form, to k4Decay, to k5PulseCount,
             to k6PulseFactor, to i7fn]
              ++ map to i0init