-- | Scanned Synthesis
module CsoundExpr.Opcodes.Siggen.ScanTop
    (scanhammer,
     scans,
     scantable,
     scanu,
     xscanmap,
     xscans,
     xscansmap,
     xscanu)
where



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



-- | * opcode : scanhammer
--  
--  
-- * syntax : 
--  
--  >   scanhammer isrc, idst, ipos, imult
--  
--  
-- * description : 
--  
--  This is is a variant of tablecopy, copying from one table to
-- another, starting at ipos, and with a gain control. The number of
-- points copied is determined by the length of the source. Other
-- points are not changed. This opcode can be used to hit a string
-- in the scanned synthesis code.
--  
--  
-- * url : <http://www.csounds.com/manual/html/scanhammer.html>
 
scanhammer :: Irate -> Irate -> Irate -> Irate -> SignalOut
scanhammer i0src i1dst i2pos i3mult = outOpcode "scanhammer" args
  where args = [to i0src, to i1dst, to i2pos, to i3mult]


-- | * opcode : scans
--  
--  
-- * syntax : 
--  
--  >   ares scans kamp, kfreq, ifn, id [, iorder]
--  
--  
-- * description : 
--  
--  Generate audio output using scanned synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/scans.html>
 
scans ::
        (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Irate -> Arate
scans i0init k1amp k2freq i3fn i4d = opcode "scans" args
  where args
          = [to k1amp, to k2freq, to i3fn, to i4d] ++ map to i0init


-- | * opcode : scantable
--  
--  
-- * syntax : 
--  
--  >   aout scantable kamp, kpch, ipos, imass, istiff, idamp, ivel
--  
--  
-- * description : 
--  
--  A simpler scanned synthesis implementation. This is an
-- implementation of a circular string scanned using external
-- tables. This opcode will allow direct modification and reading of
-- values with the table opcodes.
--  
--  
-- * url : <http://www.csounds.com/manual/html/scantable.html>
 
scantable ::
            (K k0, K k1) =>
            k0 -> k1 -> Irate -> Irate -> Irate -> Irate -> Irate -> Arate
scantable k0amp k1pch i2pos i3mass i4stiff i5damp i6vel
  = opcode "scantable" args
  where args
          = [to k0amp, to k1pch, to i2pos, to i3mass, to i4stiff, to i5damp,
             to i6vel]


-- | * opcode : scanu
--  
--  
-- * syntax : 
--  
--  >   scanu init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, 
--  >       kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id
--  
--  
-- * description : 
--  
--  Compute the waveform and the wavetable for use in scanned
-- synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/scanu.html>
 
scanu ::
        (K k0, K k1, K k2, K k3, K k4, K k5) =>
        Irate ->
          Irate ->
            Irate ->
              Irate ->
                Irate ->
                  Irate ->
                    Irate ->
                      k0 ->
                        k1 ->
                          k2 ->
                            k3 ->
                              Irate -> Irate -> k4 -> k5 -> Arate -> Irate -> Irate -> SignalOut
scanu i0nit i1rate i2fnvel i3fnmass i4fnstif i5fncentr i6fndamp
  k7mass k8stif k9centr k10damp i11left i12right k13pos k14strngth
  a15in i16disp i17d = outOpcode "scanu" args
  where args
          = [to i0nit, to i1rate, to i2fnvel, to i3fnmass, to i4fnstif,
             to i5fncentr, to i6fndamp, to k7mass, to k8stif, to k9centr,
             to k10damp, to i11left, to i12right, to k13pos, to k14strngth,
             to a15in, to i16disp, to i17d]


-- | * opcode : xscanmap
--  
--  
-- * syntax : 
--  
--  >   kpos, kvel xscanmap iscan, kamp, kvamp [, iwhich]
--  
--  
-- * description : 
--  
--  Allows the position and velocity of a node in a scanned process
-- to be read.
--  
--  
-- * url : <http://www.csounds.com/manual/html/xscanmap.html>
 
xscanmap ::
           (K k0, K k1) => [Irate] -> Irate -> k0 -> k1 -> MultiOut
xscanmap i0init i1scan k2amp k3vamp = opcode "xscanmap" args
  where args = [to i1scan, to k2amp, to k3vamp] ++ map to i0init


-- | * opcode : xscans
--  
--  
-- * syntax : 
--  
--  >   ares xscans kamp, kfreq, ifntraj, id [, iorder]
--  
--  
-- * description : 
--  
--  Experimental version of scans. Allows much larger matrices and
-- is faster and smaller but removes some (unused?) flexibility. If
-- liked, it will replace the older opcode as it is syntax
-- compatible but extended.
--  
--  
-- * url : <http://www.csounds.com/manual/html/xscans.html>
 
xscans ::
         (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> Irate -> Arate
xscans i0init k1amp k2freq i3fntraj i4d = opcode "xscans" args
  where args
          = [to k1amp, to k2freq, to i3fntraj, to i4d] ++ map to i0init


-- | * opcode : xscansmap
--  
--  
-- * syntax : 
--  
--  >   xscansmap kpos, kvel, iscan, kamp, kvamp [, iwhich]
--  
--  
-- * description : 
--  
--  Allows the position and velocity of a node in a scanned process
-- to be read.
--  
--  
-- * url : <http://www.csounds.com/manual/html/xscansmap.html>
 
xscansmap ::
            (K k0, K k1, K k2, K k3) =>
            [Irate] -> k0 -> k1 -> Irate -> k2 -> k3 -> SignalOut
xscansmap i0init k1pos k2vel i3scan k4amp k5vamp
  = outOpcode "xscansmap" args
  where args
          = [to k1pos, to k2vel, to i3scan, to k4amp, to k5vamp] ++
              map to i0init


-- | * opcode : xscanu
--  
--  
-- * syntax : 
--  
--  >   xscanu init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, 
--  >       kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id
--  
--  
-- * description : 
--  
--  Experimental version of scanu. Allows much larger matrices and
-- is faster and smaller but removes some (unused?) flexibility. If
-- liked, it will replace the older opcode as it is syntax
-- compatible but extended.
--  
--  
-- * url : <http://www.csounds.com/manual/html/xscanu.html>
 
xscanu ::
         (K k0, K k1, K k2, K k3, K k4, K k5) =>
         Irate ->
           Irate ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate ->
                     Irate ->
                       k0 ->
                         k1 ->
                           k2 ->
                             k3 ->
                               Irate -> Irate -> k4 -> k5 -> Arate -> Irate -> Irate -> SignalOut
xscanu i0nit i1rate i2fnvel i3fnmass i4fnstif i5fncentr i6fndamp
  k7mass k8stif k9centr k10damp i11left i12right k13pos k14strngth
  a15in i16disp i17d = outOpcode "xscanu" args
  where args
          = [to i0nit, to i1rate, to i2fnvel, to i3fnmass, to i4fnstif,
             to i5fncentr, to i6fndamp, to k7mass, to k8stif, to k9centr,
             to k10damp, to i11left, to i12right, to k13pos, to k14strngth,
             to a15in, to i16disp, to i17d]