-- | Models and Emulations
module CsoundExpr.Opcodes.Siggen.Models
    (bamboo,
     barmodel,
     cabasa,
     crunch,
     dripwater,
     gogobel,
     guiro,
     mandol,
     marimba,
     moog,
     sandpaper,
     sekere,
     shaker,
     sleighbells,
     stix,
     tambourine,
     vibes,
     voice,
     lorenz,
     planet,
     prepiano,
     prepianoA,
     mandel,
     chuap)
where



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



-- | * opcode : bamboo
--  
--  
-- * syntax : 
--  
--  >   ares bamboo kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] 
--  >       [, ifreq1] [, ifreq2]
--  
--  
-- * description : 
--  
--  bamboo is a semi-physical model of a bamboo sound. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bamboo.html>
 
bamboo :: (K k0) => [Irate] -> k0 -> Irate -> Arate
bamboo i0init k1amp i2dettack = opcode "bamboo" args
  where args = [to k1amp, to i2dettack] ++ map to i0init


-- | * opcode : barmodel
--  
--  
-- * syntax : 
--  
--  >   ares barmodel kbcL, kbcR, iK, ib, kscan, iT30, ipos, ivel, iwid
--  
--  
-- * description : 
--  
--  Audio output is a tone similar to a struck metal bar, using a
-- physical model developed from solving the partial differential
-- equation. There are controls over the boundary conditions as well
-- as the bar characteristics.
--  
--  
-- * url : <http://www.csounds.com/manual/html/barmodel.html>
 
barmodel ::
           (K k0, K k1, K k2) =>
           k0 ->
             k1 ->
               Irate -> Irate -> k2 -> Irate -> Irate -> Irate -> Irate -> Arate
barmodel k0bcL k1bcR i2K i3b k4scan i5T30 i6pos i7vel i8wid
  = opcode "barmodel" args
  where args
          = [to k0bcL, to k1bcR, to i2K, to i3b, to k4scan, to i5T30,
             to i6pos, to i7vel, to i8wid]


-- | * opcode : cabasa
--  
--  
-- * syntax : 
--  
--  >   ares cabasa iamp, idettack [, inum] [, idamp] [, imaxshake]
--  
--  
-- * description : 
--  
--  cabasa is a semi-physical model of a cabasa sound. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/cabasa.html>
 
cabasa :: [Irate] -> Irate -> Irate -> Arate
cabasa i0init i1amp i2dettack = opcode "cabasa" args
  where args = [to i1amp, to i2dettack] ++ map to i0init


-- | * opcode : crunch
--  
--  
-- * syntax : 
--  
--  >   ares crunch iamp, idettack [, inum] [, idamp] [, imaxshake]
--  
--  
-- * description : 
--  
--  crunch is a semi-physical model of a crunch sound. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/crunch.html>
 
crunch :: [Irate] -> Irate -> Irate -> Arate
crunch i0init i1amp i2dettack = opcode "crunch" args
  where args = [to i1amp, to i2dettack] ++ map to i0init


-- | * opcode : dripwater
--  
--  
-- * syntax : 
--  
--  >   ares dripwater kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] 
--  >       [, ifreq1] [, ifreq2]
--  
--  
-- * description : 
--  
--  dripwater is a semi-physical model of a water drop. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/dripwater.html>
 
dripwater :: (K k0) => [Irate] -> k0 -> Irate -> Arate
dripwater i0init k1amp i2dettack = opcode "dripwater" args
  where args = [to k1amp, to i2dettack] ++ map to i0init


-- | * opcode : gogobel
--  
--  
-- * syntax : 
--  
--  >   ares gogobel kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivfn
--  
--  
-- * description : 
--  
--  Audio output is a tone related to the striking of a cow bell or
-- similar. The method is a physical model developed from Perry
-- Cook, but re-coded for Csound.
--  
--  
-- * url : <http://www.csounds.com/manual/html/gogobel.html>
 
gogobel ::
          (K k0, K k1, K k2, K k3) =>
          k0 -> k1 -> Irate -> Irate -> Irate -> k2 -> k3 -> Irate -> Arate
gogobel k0amp k1freq i2hrd i3pos i4mp k5vibf k6vamp i7vfn
  = opcode "gogobel" args
  where args
          = [to k0amp, to k1freq, to i2hrd, to i3pos, to i4mp, to k5vibf,
             to k6vamp, to i7vfn]


-- | * opcode : guiro
--  
--  
-- * syntax : 
--  
--  >   ares guiro kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] [, ifreq1]
--  
--  
-- * description : 
--  
--  guiro is a semi-physical model of a guiro sound. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/guiro.html>
 
guiro :: (K k0) => [Irate] -> k0 -> Irate -> Arate
guiro i0init k1amp i2dettack = opcode "guiro" args
  where args = [to k1amp, to i2dettack] ++ map to i0init


-- | * opcode : mandol
--  
--  
-- * syntax : 
--  
--  >   ares mandol kamp, kfreq, kpluck, kdetune, kgain, ksize, ifn [, iminfreq]
--  
--  
-- * description : 
--  
--  An emulation of a mandolin.
--  
--  
-- * url : <http://www.csounds.com/manual/html/mandol.html>
 
mandol ::
         (K k0, K k1, K k2, K k3, K k4, K k5) =>
         [Irate] -> k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> Irate -> Arate
mandol i0init k1amp k2freq k3pluck k4detune k5gain k6size i7fn
  = opcode "mandol" args
  where args
          = [to k1amp, to k2freq, to k3pluck, to k4detune, to k5gain,
             to k6size, to i7fn]
              ++ map to i0init


-- | * opcode : marimba
--  
--  
-- * syntax : 
--  
--  >   ares marimba kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec 
--  >       [, idoubles] [, itriples]
--  
--  
-- * description : 
--  
--  Audio output is a tone related to the striking of a wooden block
-- as found in a marimba. The method is a physical model developed
-- from Perry Cook but re-coded for Csound.
--  
--  
-- * url : <http://www.csounds.com/manual/html/marimba.html>
 
marimba ::
          (K k0, K k1, K k2, K k3) =>
          [Irate] ->
            k0 ->
              k1 ->
                Irate -> Irate -> Irate -> k2 -> k3 -> Irate -> Irate -> Arate
marimba i0init k1amp k2freq i3hrd i4pos i5mp k6vibf k7vamp i8vibfn
  i9dec = opcode "marimba" args
  where args
          = [to k1amp, to k2freq, to i3hrd, to i4pos, to i5mp, to k6vibf,
             to k7vamp, to i8vibfn, to i9dec]
              ++ map to i0init


-- | * opcode : moog
--  
--  
-- * syntax : 
--  
--  >   ares moog kamp, kfreq, kfiltq, kfiltrate, kvibf, kvamp, iafn, iwfn, ivfn
--  
--  
-- * description : 
--  
--  An emulation of a mini-Moog synthesizer.
--  
--  
-- * url : <http://www.csounds.com/manual/html/moog.html>
 
moog ::
       (K k0, K k1, K k2, K k3, K k4, K k5) =>
       k0 ->
         k1 -> k2 -> k3 -> k4 -> k5 -> Irate -> Irate -> Irate -> Arate
moog k0amp k1freq k2filtq k3filtrate k4vibf k5vamp i6afn i7wfn
  i8vfn = opcode "moog" args
  where args
          = [to k0amp, to k1freq, to k2filtq, to k3filtrate, to k4vibf,
             to k5vamp, to i6afn, to i7wfn, to i8vfn]


-- | * opcode : sandpaper
--  
--  
-- * syntax : 
--  
--  >   ares sandpaper iamp, idettack [, inum] [, idamp] [, imaxshake]
--  
--  
-- * description : 
--  
--  sandpaper is a semi-physical model of a sandpaper sound. It is
-- one of the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sandpaper.html>
 
sandpaper :: [Irate] -> Irate -> Irate -> Arate
sandpaper i0init i1amp i2dettack = opcode "sandpaper" args
  where args = [to i1amp, to i2dettack] ++ map to i0init


-- | * opcode : sekere
--  
--  
-- * syntax : 
--  
--  >   ares sekere iamp, idettack [, inum] [, idamp] [, imaxshake]
--  
--  
-- * description : 
--  
--  sekere is a semi-physical model of a sekere sound. It is one of
-- the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sekere.html>
 
sekere :: [Irate] -> Irate -> Irate -> Arate
sekere i0init i1amp i2dettack = opcode "sekere" args
  where args = [to i1amp, to i2dettack] ++ map to i0init


-- | * opcode : shaker
--  
--  
-- * syntax : 
--  
--  >   ares shaker kamp, kfreq, kbeans, kdamp, ktimes [, idecay]
--  
--  
-- * description : 
--  
--  Audio output is a tone related to the shaking of a maraca or
-- similar gourd instrument. The method is a physically inspired
-- model developed from Perry Cook, but re-coded for Csound.
--  
--  
-- * url : <http://www.csounds.com/manual/html/shaker.html>
 
shaker ::
         (K k0, K k1, K k2, K k3, K k4) =>
         [Irate] -> k0 -> k1 -> k2 -> k3 -> k4 -> Arate
shaker i0init k1amp k2freq k3beans k4damp k5times
  = opcode "shaker" args
  where args
          = [to k1amp, to k2freq, to k3beans, to k4damp, to k5times] ++
              map to i0init


-- | * opcode : sleighbells
--  
--  
-- * syntax : 
--  
--  >   ares sleighbells kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] 
--  >       [, ifreq1] [, ifreq2]
--  
--  
-- * description : 
--  
--  sleighbells is a semi-physical model of a sleighbell sound. It
-- is one of the PhISEM percussion opcodes. PhISEM (Physically
-- Informed Stochastic Event Modeling) is an algorithmic approach
-- for simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sleighbells.html>
 
sleighbells :: (K k0) => [Irate] -> k0 -> Irate -> Arate
sleighbells i0init k1amp i2dettack = opcode "sleighbells" args
  where args = [to k1amp, to i2dettack] ++ map to i0init


-- | * opcode : stix
--  
--  
-- * syntax : 
--  
--  >   ares stix iamp, idettack [, inum] [, idamp] [, imaxshake]
--  
--  
-- * description : 
--  
--  stix is a semi-physical model of a stick sound. It is one of the
-- PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic
-- Event Modeling) is an algorithmic approach for simulating
-- collisions of multiple independent sound producing objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/stix.html>
 
stix :: [Irate] -> Irate -> Irate -> Arate
stix i0init i1amp i2dettack = opcode "stix" args
  where args = [to i1amp, to i2dettack] ++ map to i0init


-- | * opcode : tambourine
--  
--  
-- * syntax : 
--  
--  >   ares tambourine kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] 
--  >       [, ifreq1] [, ifreq2]
--  
--  
-- * description : 
--  
--  tambourine is a semi-physical model of a tambourine sound. It is
-- one of the PhISEM percussion opcodes. PhISEM (Physically Informed
-- Stochastic Event Modeling) is an algorithmic approach for
-- simulating collisions of multiple independent sound producing
-- objects.
--  
--  
-- * url : <http://www.csounds.com/manual/html/tambourine.html>
 
tambourine :: (K k0) => [Irate] -> k0 -> Irate -> Arate
tambourine i0init k1amp i2dettack = opcode "tambourine" args
  where args = [to k1amp, to i2dettack] ++ map to i0init


-- | * opcode : vibes
--  
--  
-- * syntax : 
--  
--  >   ares vibes kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec
--  
--  
-- * description : 
--  
--  Audio output is a tone related to the striking of a metal block
-- as found in a vibraphone. The method is a physical model
-- developed from Perry Cook, but re-coded for Csound.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vibes.html>
 
vibes ::
        (K k0, K k1, K k2, K k3) =>
        k0 ->
          k1 ->
            Irate -> Irate -> Irate -> k2 -> k3 -> Irate -> Irate -> Arate
vibes k0amp k1freq i2hrd i3pos i4mp k5vibf k6vamp i7vibfn i8dec
  = opcode "vibes" args
  where args
          = [to k0amp, to k1freq, to i2hrd, to i3pos, to i4mp, to k5vibf,
             to k6vamp, to i7vibfn, to i8dec]


-- | * opcode : voice
--  
--  
-- * syntax : 
--  
--  >   ares voice kamp, kfreq, kphoneme, kform, kvibf, kvamp, ifn, ivfn
--  
--  
-- * description : 
--  
--  An emulation of a human voice.
--  
--  
-- * url : <http://www.csounds.com/manual/html/voice.html>
 
voice ::
        (K k0, K k1, K k2, K k3, K k4, K k5) =>
        k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> Irate -> Irate -> Arate
voice k0amp k1freq k2phoneme k3form k4vibf k5vamp i6fn i7vfn
  = opcode "voice" args
  where args
          = [to k0amp, to k1freq, to k2phoneme, to k3form, to k4vibf,
             to k5vamp, to i6fn, to i7vfn]


-- | * opcode : lorenz
--  
--  
-- * syntax : 
--  
--  >   ax, ay, az lorenz ksv, krv, kbv, kh, ix, iy, iz, iskip [, iskipinit]
--  
--  
-- * description : 
--  
--  Implements the Lorenz system of equations. The Lorenz system is
-- a chaotic-dynamic system which was originally used to simulate
-- the motion of a particle in convection currents and simplified
-- weather systems. Small differences in initial conditions rapidly
-- lead to diverging values. This is sometimes expressed as the
-- butterfly effect. If a butterfly flaps its wings in Australia, it
-- will have an effect on the weather in Alaska. This system is one
-- of the milestones in the development of chaos theory. It is
-- useful as a chaotic audio source or as a low frequency modulation
-- source.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lorenz.html>
 
lorenz ::
         (K k0, K k1, K k2, K k3) =>
         [Irate] ->
           k0 ->
             k1 -> k2 -> k3 -> Irate -> Irate -> Irate -> Irate -> MultiOut
lorenz i0init k1sv k2rv k3bv k4h i5x i6y i7z i8skip
  = opcode "lorenz" args
  where args
          = [to k1sv, to k2rv, to k3bv, to k4h, to i5x, to i6y, to i7z,
             to i8skip]
              ++ map to i0init


-- | * opcode : planet
--  
--  
-- * syntax : 
--  
--  >   ax, ay, az planet kmass1, kmass2, ksep, ix, iy, iz, ivx, ivy, ivz, idelta 
--  >       [, ifriction] [, iskip]
--  
--  
-- * description : 
--  
--  planet simulates a planet orbiting in a binary star system. The
-- outputs are the x, y and z coordinates of the orbiting planet. It
-- is possible for the planet to achieve escape velocity by a close
-- encounter with a star. This makes this system somewhat unstable.
--  
--  
-- * url : <http://www.csounds.com/manual/html/planet.html>
 
planet ::
         (K k0, K k1, K k2) =>
         [Irate] ->
           k0 ->
             k1 ->
               k2 ->
                 Irate ->
                   Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
planet i0init k1mass1 k2mass2 k3sep i4x i5y i6z i7vx i8vy i9vz
  i10delta = opcode "planet" args
  where args
          = [to k1mass1, to k2mass2, to k3sep, to i4x, to i5y, to i6z,
             to i7vx, to i8vy, to i9vz, to i10delta]
              ++ map to i0init


-- | * opcode : prepiano
--  
--  
-- * syntax : 
--  
--  >   ares prepiano ifreq, iNS, iD, iK, 
--  >       iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, 
--  >       isspread[, irattles, irubbers]
--  >   al,ar prepiano ifreq, iNS, iD, iK, 
--  >       iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, 
--  >       isspread[, irattles, irubbers]
--  
--  
-- * description : 
--  
--  Audio output is a tone similar to a piano string, prepared with
-- a number of rubbers and rattles. The method uses a physical model
-- developed from solving the partial differential equation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/prepiano.html>
 
prepiano ::
           (K k0, K k1) =>
           [Irate] ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate ->
                     Irate ->
                       Irate ->
                         k0 ->
                           k1 ->
                             Irate ->
                               Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
prepiano i0init i1freq i2NS i3D i4K i5T30 i6B k7bcl k8bcr i9mass
  i10freq i11init i12pos i13vel i14sfreq i15sspread
  = opcode "prepiano" args
  where args
          = [to i1freq, to i2NS, to i3D, to i4K, to i5T30, to i6B, to k7bcl,
             to k8bcr, to i9mass, to i10freq, to i11init, to i12pos, to i13vel,
             to i14sfreq, to i15sspread]
              ++ map to i0init


-- | * opcode : prepiano
--  
--  
-- * syntax : 
--  
--  >   ares prepiano ifreq, iNS, iD, iK, 
--  >       iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, 
--  >       isspread[, irattles, irubbers]
--  >   al,ar prepiano ifreq, iNS, iD, iK, 
--  >       iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, 
--  >       isspread[, irattles, irubbers]
--  
--  
-- * description : 
--  
--  Audio output is a tone similar to a piano string, prepared with
-- a number of rubbers and rattles. The method uses a physical model
-- developed from solving the partial differential equation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/prepiano.html>
 
prepianoA ::
            (K k0, K k1) =>
            [Irate] ->
              Irate ->
                Irate ->
                  Irate ->
                    Irate ->
                      Irate ->
                        Irate ->
                          k0 ->
                            k1 ->
                              Irate ->
                                Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Arate
prepianoA i0init i1freq i2NS i3D i4K i5T30 i6B k7bcl k8bcr i9mass
  i10freq i11init i12pos i13vel i14sfreq i15sspread
  = opcode "prepiano" args
  where args
          = [to i1freq, to i2NS, to i3D, to i4K, to i5T30, to i6B, to k7bcl,
             to k8bcr, to i9mass, to i10freq, to i11init, to i12pos, to i13vel,
             to i14sfreq, to i15sspread]
              ++ map to i0init


-- | * opcode : mandel
--  
--  
-- * syntax : 
--  
--  >   kiter, koutrig mandel ktrig, kx, ky, kmaxIter
--  
--  
-- * description : 
--  
--  Returns the number of iterations corresponding to a given point
-- of complex plane by applying the Mandelbrot set formula.
--  
--  
-- * url : <http://www.csounds.com/manual/html/mandel.html>
 
mandel ::
         (K k0, K k1, K k2, K k3) => k0 -> k1 -> k2 -> k3 -> MultiOut
mandel k0trig k1x k2y k3maxIter = opcode "mandel" args
  where args = [to k0trig, to k1x, to k2y, to k3maxIter]


-- | * opcode : chuap
--  
--  
-- * syntax : 
--  
--  >   aI3, aV2, aV1 chuap kL, kR0, kC1, kG, kGa, kGb, kE, kC2, iI3, iV2, iV1, ktime_step
--  
--  
-- * description : 
--  
--  Simulates Chua's oscillator, an LRC oscillator with an active
-- resistor, proved capable of bifurcation and chaotic attractors,
-- with k-rate control of circuit elements.
--  
--  
-- * url : <http://www.csounds.com/manual/html/chuap.html>
 
chuap ::
        (K k0, K k1, K k2, K k3, K k4, K k5, K k6, K k7, K k8) =>
        k0 ->
          k1 ->
            k2 ->
              k3 ->
                k4 -> k5 -> k6 -> k7 -> Irate -> Irate -> Irate -> k8 -> MultiOut
chuap k0L k1R0 k2C1 k3G k4Ga k5Gb k6E k7C2 i8I3 i9V2 i10V1
  k11time_step = opcode "chuap" args
  where args
          = [to k0L, to k1R0, to k2C1, to k3G, to k4Ga, to k5Gb, to k6E,
             to k7C2, to i8I3, to i9V2, to i10V1, to k11time_step]