-- | Panning and Spatialization
module CsoundExpr.Opcodes.Sigmod.Panspatl
    (locsend,
     locsig,
     pan,
     pan2,
     space,
     spdist,
     spsend,
     spat3d,
     spat3di,
     spat3dt,
     vbap16,
     vbap16move,
     vbap4,
     vbap4move,
     vbap8,
     vbap8move,
     vbaplsinit,
     vbapz,
     vbapzmove,
     hrtfer,
     hrtfmove,
     hrtfmove2,
     hrtfstat,
     bformdec,
     bformenc,
     bformencK)
where



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



-- | * opcode : locsend
--  
--  
-- * syntax : 
--  
--  >   a1, a2 locsend
--  >   a1, a2, a3, a4 locsend
--  
--  
-- * description : 
--  
--  locsend depends upon the existence of a previously defined
-- locsig. The number of output signals must match the number in the
-- previous locsig. The output signals from locsend are derived from
-- the values given for distance and reverb in the locsig and are
-- ready to be sent to local or global reverb units (see example
-- below). The reverb amount and the balance between the 2 or 4
-- channels are calculated in the same way as described in the Dodge
-- book (an essential text!).
--  
--  
-- * url : <http://www.csounds.com/manual/html/locsend.html>
 
locsend :: MultiOut
locsend = opcode "locsend" args
  where args = []


-- | * opcode : locsig
--  
--  
-- * syntax : 
--  
--  >   a1, a2 locsig asig, kdegree, kdistance, kreverbsend
--  >   a1, a2, a3, a4 locsig asig, kdegree, kdistance, kreverbsend
--  
--  
-- * description : 
--  
--  locsig takes an input signal and distributes it among 2 or 4
-- channels using values in degrees to calculate the balance between
-- adjacent channels. It also takes arguments for distance (used to
-- attenuate signals that are to sound as if they are some distance
-- further than the loudspeaker itself), and for the amount the
-- signal that will be sent to reverberators. This unit is based
-- upon the example in the Charles Dodge/Thomas Jerse book, Computer
-- Music, page 320.
--  
--  
-- * url : <http://www.csounds.com/manual/html/locsig.html>
 
locsig :: (K k0, K k1, K k2) => Arate -> k0 -> k1 -> k2 -> MultiOut
locsig a0sig k1degree k2distance k3reverbsend
  = opcode "locsig" args
  where args
          = [to a0sig, to k1degree, to k2distance, to k3reverbsend]


-- | * opcode : pan
--  
--  
-- * syntax : 
--  
--  >   a1, a2, a3, a4 pan asig, kx, ky, ifn [, imode] [, ioffset]
--  
--  
-- * description : 
--  
--  Distribute an audio signal amongst four channels with
-- localization control.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pan.html>
 
pan ::
      (K k0, K k1) => [Irate] -> Arate -> k0 -> k1 -> Irate -> MultiOut
pan i0init a1sig k2x k3y i4fn = opcode "pan" args
  where args = [to a1sig, to k2x, to k3y, to i4fn] ++ map to i0init


-- | * opcode : pan2
--  
--  
-- * syntax : 
--  
--  >   a1, a2 pan2 asig, xp [, imode]
--  
--  
-- * description : 
--  
--  Distribute an audio signal across two channels with a choice of
-- methods.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pan2.html>
 
pan2 :: (X x0) => [Irate] -> Arate -> x0 -> MultiOut
pan2 i0init a1sig x2p = opcode "pan2" args
  where args = [to a1sig, to x2p] ++ map to i0init


-- | * opcode : space
--  
--  
-- * syntax : 
--  
--  >   a1, a2, a3, a4 space asig, ifn, ktime, kreverbsend, kx, ky
--  
--  
-- * description : 
--  
--  space takes an input signal and distributes it among 4 channels
-- using Cartesian xy coordinates to calculate the balance of the
-- outputs. The xy coordinates can be defined in a separate text
-- file and accessed through a Function statement in the score using
-- Gen28, or they can be specified using the optional kx, ky
-- arguments. The advantages to the former are:
--  
--  
-- * url : <http://www.csounds.com/manual/html/space.html>
 
space ::
        (K k0, K k1, K k2, K k3) =>
        Arate -> Irate -> k0 -> k1 -> k2 -> k3 -> MultiOut
space a0sig i1fn k2time k3reverbsend k4x k5y = opcode "space" args
  where args
          = [to a0sig, to i1fn, to k2time, to k3reverbsend, to k4x, to k5y]


-- | * opcode : spdist
--  
--  
-- * syntax : 
--  
--  >   k1 spdist ifn, ktime, kx, ky
--  
--  
-- * description : 
--  
--  spdist uses the same xy data as space, also either from a text
-- file using Gen28 or from x and y arguments given to the unit
-- directly. The purpose of this unit is to make available the
-- values for distance that are calculated from the xy coordinates.
--  
--  
-- * url : <http://www.csounds.com/manual/html/spdist.html>
 
spdist :: (K k0, K k1, K k2) => Irate -> k0 -> k1 -> k2 -> Krate
spdist i0fn k1time k2x k3y = opcode "spdist" args
  where args = [to i0fn, to k1time, to k2x, to k3y]


-- | * opcode : spsend
--  
--  
-- * syntax : 
--  
--  >   a1, a2, a3, a4 spsend
--  
--  
-- * description : 
--  
--  spsend depends upon the existence of a previously defined space.
-- The output signals from spsend are derived from the values given
-- for xy and reverb in the space and are ready to be sent to local
-- or global reverb units (see example below).
--  
--  
-- * url : <http://www.csounds.com/manual/html/spsend.html>
 
spsend :: MultiOut
spsend = opcode "spsend" args
  where args = []


-- | * opcode : spat3d
--  
--  
-- * syntax : 
--  
--  >   aW, aX, aY, aZ spat3d ain, kX, kY, kZ, idist, ift, imode, imdel, iovr [, istor]
--  
--  
-- * description : 
--  
--  This opcode positions the input sound in a 3D space, with
-- optional simulation of room acoustics, in various output formats.
-- spat3d allows moving the sound at k-rate (this movement is
-- interpolated internally to eliminate "zipper noise" if sr not
-- equal to kr).
--  
--  
-- * url : <http://www.csounds.com/manual/html/spat3d.html>
 
spat3d ::
         (K k0, K k1, K k2) =>
         [Irate] ->
           Arate ->
             k0 ->
               k1 -> k2 -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
spat3d i0init a1in k2X k3Y k4Z i5dist i6ft i7mode i8mdel i9ovr
  = opcode "spat3d" args
  where args
          = [to a1in, to k2X, to k3Y, to k4Z, to i5dist, to i6ft, to i7mode,
             to i8mdel, to i9ovr]
              ++ map to i0init


-- | * opcode : spat3di
--  
--  
-- * syntax : 
--  
--  >   aW, aX, aY, aZ spat3di ain, iX, iY, iZ, idist, ift, imode [, istor]
--  
--  
-- * description : 
--  
--  This opcode positions the input sound in a 3D space, with
-- optional simulation of room acoustics, in various output formats.
-- With spat3di, sound source position is set at i-time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/spat3di.html>
 
spat3di ::
          [Irate] ->
            Arate ->
              Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
spat3di i0init a1in i2X i3Y i4Z i5dist i6ft i7mode
  = opcode "spat3di" args
  where args
          = [to a1in, to i2X, to i3Y, to i4Z, to i5dist, to i6ft, to i7mode]
              ++ map to i0init


-- | * opcode : spat3dt
--  
--  
-- * syntax : 
--  
--  >   spat3dt ioutft, iX, iY, iZ, idist, ift, imode, irlen [, iftnocl]
--  
--  
-- * description : 
--  
--  This opcode positions the input sound in a 3D space, with
-- optional simulation of room acoustics, in various output formats.
-- spat3dt can be used to render the impulse response at i-time,
-- storing output in a function table, suitable for convolution.
--  
--  
-- * url : <http://www.csounds.com/manual/html/spat3dt.html>
 
spat3dt ::
          [Irate] ->
            Irate ->
              Irate ->
                Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> SignalOut
spat3dt i0init i1outft i2X i3Y i4Z i5dist i6ft i7mode i8rlen
  = outOpcode "spat3dt" args
  where args
          = [to i1outft, to i2X, to i3Y, to i4Z, to i5dist, to i6ft,
             to i7mode, to i8rlen]
              ++ map to i0init


-- | * opcode : vbap16
--  
--  
-- * syntax : 
--  
--  >   ar1,..., ar16 vbap16 asig, kazim [, kelev] [, kspread]
--  
--  
-- * description : 
--  
--  Distributes an audio signal among 16 channels.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap16.html>
 
vbap16 :: (K k0, K k1) => [k0] -> Arate -> k1 -> MultiOut
vbap16 k0init a1sig k2azim = opcode "vbap16" args
  where args = [to a1sig, to k2azim] ++ map to k0init


-- | * opcode : vbap16move
--  
--  
-- * syntax : 
--  
--  >   ar1,..., ar16 vbap16move asig, idur, ispread, ifldnum, ifld1 
--  >       [, ifld2] [...]
--  
--  
-- * description : 
--  
--  Distribute an audio signal among 16 channels with moving virtual
-- sources.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap16move.html>
 
vbap16move ::
             Arate -> Irate -> Irate -> Irate -> [Irate] -> MultiOut
vbap16move a0sig i1dur i2spread i3fldnum i4fldN
  = opcode "vbap16move" args
  where args
          = [to a0sig, to i1dur, to i2spread, to i3fldnum] ++ map to i4fldN


-- | * opcode : vbap4
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2, ar3, ar4 vbap4 asig, kazim [, kelev] [, kspread]
--  
--  
-- * description : 
--  
--  Distributes an audio signal among 4 channels.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap4.html>
 
vbap4 :: (K k0, K k1) => [k0] -> Arate -> k1 -> MultiOut
vbap4 k0init a1sig k2azim = opcode "vbap4" args
  where args = [to a1sig, to k2azim] ++ map to k0init


-- | * opcode : vbap4move
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2, ar3, ar4 vbap4move asig, idur, ispread, ifldnum, ifld1 
--  >       [, ifld2] [...]
--  
--  
-- * description : 
--  
--  Distributes an audio signal among 4 channels with moving virtual
-- sources.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap4move.html>
 
vbap4move ::
            Arate -> Irate -> Irate -> Irate -> [Irate] -> MultiOut
vbap4move a0sig i1dur i2spread i3fldnum i4fldN
  = opcode "vbap4move" args
  where args
          = [to a0sig, to i1dur, to i2spread, to i3fldnum] ++ map to i4fldN


-- | * opcode : vbap8
--  
--  
-- * syntax : 
--  
--  >   ar1,..., ar8 vbap8 asig, kazim [, kelev] [, kspread]
--  
--  
-- * description : 
--  
--  Distributes an audio signal among 8 channels.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap8.html>
 
vbap8 :: (K k0, K k1) => [k0] -> Arate -> k1 -> MultiOut
vbap8 k0init a1sig k2azim = opcode "vbap8" args
  where args = [to a1sig, to k2azim] ++ map to k0init


-- | * opcode : vbap8move
--  
--  
-- * syntax : 
--  
--  >   ar1,..., ar8 vbap8move asig, idur, ispread, ifldnum, ifld1 
--  >       [, ifld2] [...]
--  
--  
-- * description : 
--  
--  Distributes an audio signal among 8 channels with moving virtual
-- sources.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbap8move.html>
 
vbap8move ::
            Arate -> Irate -> Irate -> Irate -> [Irate] -> MultiOut
vbap8move a0sig i1dur i2spread i3fldnum i4fldN
  = opcode "vbap8move" args
  where args
          = [to a0sig, to i1dur, to i2spread, to i3fldnum] ++ map to i4fldN


-- | * opcode : vbaplsinit
--  
--  
-- * syntax : 
--  
--  >   vbaplsinit idim, ilsnum [, idir1] [, idir2] [...] [, idir32]
--  
--  
-- * description : 
--  
--  Configures VBAP output according to loudspeaker parameters.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbaplsinit.html>
 
vbaplsinit :: Irate -> Irate -> [Irate] -> SignalOut
vbaplsinit i0dim i1lsnum i2dirN = outOpcode "vbaplsinit" args
  where args = [to i0dim, to i1lsnum] ++ map to i2dirN


-- | * opcode : vbapz
--  
--  
-- * syntax : 
--  
--  >   vbapz inumchnls, istartndx, asig, kazim [, kelev] [, kspread]
--  
--  
-- * description : 
--  
--  Writes a multi-channel audio signal to a ZAK array.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbapz.html>
 
vbapz ::
        (K k0, K k1) => [k0] -> Irate -> Irate -> Arate -> k1 -> SignalOut
vbapz k0init i1numchnls i2startndx a3sig k4azim
  = outOpcode "vbapz" args
  where args
          = [to i1numchnls, to i2startndx, to a3sig, to k4azim] ++
              map to k0init


-- | * opcode : vbapzmove
--  
--  
-- * syntax : 
--  
--  >   vbapzmove inumchnls, istartndx, asig, idur, ispread, ifldnum, ifld1, 
--  >       ifld2, [...]
--  
--  
-- * description : 
--  
--  Writes a multi-channel audio signal to a ZAK array with moving
-- virtual sources.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vbapzmove.html>
 
vbapzmove ::
            Irate ->
              Irate -> Arate -> Irate -> Irate -> Irate -> [Irate] -> SignalOut
vbapzmove i0numchnls i1startndx a2sig i3dur i4spread i5fldnum
  i6fldN = outOpcode "vbapzmove" args
  where args
          = [to i0numchnls, to i1startndx, to a2sig, to i3dur, to i4spread,
             to i5fldnum]
              ++ map to i6fldN


-- | * opcode : hrtfer
--  
--  
-- * syntax : 
--  
--  >   aleft, aright hrtfer asig, kaz, kelev, “HRTFcompact”
--  
--  
-- * description : 
--  
--  Output is binaural (headphone) 3D audio.
--  
--  
-- * url : <http://www.csounds.com/manual/html/hrtfer.html>
 
hrtfer :: (K k0, K k1) => Arate -> k0 -> k1 -> MultiOut
hrtfer a0sig k1az k2elev = opcode "hrtfer" args
  where args = [to a0sig, to k1az, to k2elev]


-- | * opcode : hrtfmove
--  
--  
-- * syntax : 
--  
--  >   aleft, aright hrtfmove asrc, kAz, kElev, ifilel, ifiler [, imode, ifade, isr]
--  
--  
-- * description : 
--  
--  This opcode takes a source signal and spatialises it in the 3
-- dimensional space around a listener by convolving the source with
-- stored head related transfer function (HRTF) based filters.
--  
--  
-- * url : <http://www.csounds.com/manual/html/hrtfmove.html>
 
hrtfmove ::
           (K k0, K k1) =>
           [Irate] -> Arate -> k0 -> k1 -> Irate -> Irate -> MultiOut
hrtfmove i0init a1src k2Az k3Elev i4filel i5filer
  = opcode "hrtfmove" args
  where args
          = [to a1src, to k2Az, to k3Elev, to i4filel, to i5filer] ++
              map to i0init


-- | * opcode : hrtfmove2
--  
--  
-- * syntax : 
--  
--  >   aleft, aright hrtfmove2 asrc, kAz, kElev, ifilel, ifiler [,ioverlap, iradius, isr]
--  
--  
-- * description : 
--  
--  This opcode takes a source signal and spatialises it in the 3
-- dimensional space around a listener using head related transfer
-- function (HRTF) based filters.
--  
--  
-- * url : <http://www.csounds.com/manual/html/hrtfmove2.html>
 
hrtfmove2 ::
            (K k0, K k1) =>
            [Irate] -> Arate -> k0 -> k1 -> Irate -> Irate -> MultiOut
hrtfmove2 i0init a1src k2Az k3Elev i4filel i5filer
  = opcode "hrtfmove2" args
  where args
          = [to a1src, to k2Az, to k3Elev, to i4filel, to i5filer] ++
              map to i0init


-- | * opcode : hrtfstat
--  
--  
-- * syntax : 
--  
--  >   aleft, aright hrtfstat asrc, iAz, iElev, ifilel, ifiler [,iradius, isr]
--  
--  
-- * description : 
--  
--  This opcode takes a source signal and spatialises it in the 3
-- dimensional space around a listener using head related transfer
-- function (HRTF) based filters. It produces a static output
-- (azimuth and elevation parameters are i-rate), because a static
-- source allows much more efficient processing than hrtfmove and
-- hrtfmove2,.
--  
--  
-- * url : <http://www.csounds.com/manual/html/hrtfstat.html>
 
hrtfstat ::
           [Irate] -> Arate -> Irate -> Irate -> Irate -> Irate -> MultiOut
hrtfstat i0init a1src i2Az i3Elev i4filel i5filer
  = opcode "hrtfstat" args
  where args
          = [to a1src, to i2Az, to i3Elev, to i4filel, to i5filer] ++
              map to i0init


-- | * opcode : bformdec
--  
--  
-- * syntax : 
--  
--  >   ao1, ao2 bformdec isetup, aw, ax, ay, az [, ar, as, at, au, av 
--  >       [, abk, al, am, an, ao, ap, aq]]
--  >   ao1, ao2, ao3, ao4 bformdec isetup, aw, ax, ay, az [, ar, as, at, 
--  >       au, av [, abk, al, am, an, ao, ap, aq]]
--  >   ao1, ao2, ao3, ao4, ao5 bformdec isetup, aw, ax, ay, az [, ar, as, 
--  >       at, au, av [, abk, al, am, an, ao, ap, aq]]
--  >   ao1, ao2, ao3, ao4, ao5, ao6, ao7, ao8 bformdec isetup, aw, ax, ay, az 
--  >       [, ar, as, at, au, av [, abk, al, am, an, ao, ap, aq]]]
--  
--  
-- * description : 
--  
--  Decodes an ambisonic B format signal into loudspeaker specific
-- signals. Note that this opcode is deprecated as it is inaccurate,
-- and is replaced by the much better opcode bformdec1 which
-- replicates all the important features.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bformdec.html>
 
bformdec ::
           [Arate] -> Irate -> Arate -> Arate -> Arate -> Arate -> MultiOut
bformdec a0init i1setup a2w a3x a4y a5z = opcode "bformdec" args
  where args
          = [to i1setup, to a2w, to a3x, to a4y, to a5z] ++ map to a0init


-- | * opcode : bformenc
--  
--  
-- * syntax : 
--  
--  >   aw, ax, ay, az bformenc asig, kalpha, kbeta, kord0, kord1
--  >   aw, ax, ay, az, ar, as, at, au, av bformenc asig, kalpha, kbeta, 
--  >       kord0, kord1, kord2
--  >   aw, ax, ay, az, ar, as, at, au, av, ak, al, am, an, ao, ap, aq bformenc 
--  >       asig, kalpha, kbeta, kord0, kord1, kord2, kord3
--  
--  
-- * description : 
--  
--  Codes a signal into the ambisonic B format. Note that this
-- opcode is deprecated as it is inaccurate, and is replaced by the
-- much better opcode bformenc1 which replicates all the important
-- features; also note that the gain arguments are not available in
-- bformenc1.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bformenc.html>
 
bformenc ::
           (K k0, K k1, K k2, K k3) =>
           Arate -> k0 -> k1 -> k2 -> k3 -> MultiOut
bformenc a0sig k1alpha k2beta k3ord0 k4ord1
  = opcode "bformenc" args
  where args
          = [to a0sig, to k1alpha, to k2beta, to k3ord0, to k4ord1]


-- | * opcode : bformenc
--  
--  
-- * syntax : 
--  
--  >   aw, ax, ay, az bformenc asig, kalpha, kbeta, kord0, kord1
--  >   aw, ax, ay, az, ar, as, at, au, av bformenc asig, kalpha, kbeta, 
--  >       kord0, kord1, kord2
--  >   aw, ax, ay, az, ar, as, at, au, av, ak, al, am, an, ao, ap, aq bformenc 
--  >       asig, kalpha, kbeta, kord0, kord1, kord2, kord3
--  
--  
-- * description : 
--  
--  Codes a signal into the ambisonic B format. Note that this
-- opcode is deprecated as it is inaccurate, and is replaced by the
-- much better opcode bformenc1 which replicates all the important
-- features; also note that the gain arguments are not available in
-- bformenc1.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bformenc.html>
 
bformencK ::
            (K k0, K k1, K k2, K k3, K k4) =>
            Arate -> k0 -> k1 -> k2 -> k3 -> k4 -> MultiOut
bformencK a0sig k1alpha k2beta k3ord0 k4ord1 k5ord2
  = opcode "bformenc" args
  where args
          = [to a0sig, to k1alpha, to k2beta, to k3ord0, to k4ord1,
             to k5ord2]