-- | Operations Between two  Vectorial Signals
module CsoundExpr.Opcodes.Vectorial.Vectorialvectorial
    (vaddv,
     vsubv,
     vmultv,
     vdivv,
     vpowv,
     vexpv,
     vcopy,
     vmap,
     vaddv_i,
     vsubv_i,
     vmultv_i,
     vdivv_i,
     vpowv_i,
     vexpv_i,
     vcopy_i)
where



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



-- | * opcode : vaddv
--  
--  
-- * syntax : 
--  
--  >   vaddv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs addition between two vectorial control signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vaddv.html>
 
vaddv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vaddv k0init i1fn1 i2fn2 k3elements = outOpcode "vaddv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vsubv
--  
--  
-- * syntax : 
--  
--  >   vsubv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs subtraction between two vectorial control signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vsubv.html>
 
vsubv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vsubv k0init i1fn1 i2fn2 k3elements = outOpcode "vsubv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vmultv
--  
--  
-- * syntax : 
--  
--  >   vmultv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs mutiplication between two vectorial control signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vmultv.html>
 
vmultv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vmultv k0init i1fn1 i2fn2 k3elements = outOpcode "vmultv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vdivv
--  
--  
-- * syntax : 
--  
--  >   vdivv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs division between two vectorial control signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vdivv.html>
 
vdivv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vdivv k0init i1fn1 i2fn2 k3elements = outOpcode "vdivv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vpowv
--  
--  
-- * syntax : 
--  
--  >   vpowv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs power-of operations between two vectorial control
-- signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vpowv.html>
 
vpowv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vpowv k0init i1fn1 i2fn2 k3elements = outOpcode "vpowv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vexpv
--  
--  
-- * syntax : 
--  
--  >   vexpv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
--  
--  
-- * description : 
--  
--  Performs exponential operations between two vectorial control
-- signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vexpv.html>
 
vexpv :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vexpv k0init i1fn1 i2fn2 k3elements = outOpcode "vexpv" args
  where args = [to i1fn1, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vcopy
--  
--  
-- * syntax : 
--  
--  >   vcopy ifn, ifn2, kelements [, kdstoffset] [, ksrcoffset] [, kverbose]
--  
--  
-- * description : 
--  
--  Copies between two vectorial control signals
--  
--  
-- * url : <http://www.csounds.com/manual/html/vcopy.html>
 
vcopy :: (K k0, K k1) => [k0] -> Irate -> Irate -> k1 -> SignalOut
vcopy k0init i1fn i2fn2 k3elements = outOpcode "vcopy" args
  where args = [to i1fn, to i2fn2, to k3elements] ++ map to k0init


-- | * opcode : vmap
--  
--  
-- * syntax : 
--  
--  >   vmap ifn1, ifn2, ielements [,idstoffset, isrcoffset]
--  
--  
-- * description : 
--  
--  Maps elements from a vector onto another according to the
-- indeces of a this vector
--  
--  
-- * url : <http://www.csounds.com/manual/html/vmap.html>
 
vmap :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vmap i0init i1fn1 i2fn2 i3elements = outOpcode "vmap" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vaddv_i
--  
--  
-- * syntax : 
--  
--  >   vaddv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs addition between two vectorial control signals at init
-- time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vaddv_i.html>
 
vaddv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vaddv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vaddv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vsubv_i
--  
--  
-- * syntax : 
--  
--  >   vsubv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs subtraction between two vectorial control signals at
-- init time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vsubv_i.html>
 
vsubv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vsubv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vsubv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vmultv_i
--  
--  
-- * syntax : 
--  
--  >   vmultv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs mutiplication between two vectorial control signals at
-- init time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vmultv_i.html>
 
vmultv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vmultv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vmultv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vdivv_i
--  
--  
-- * syntax : 
--  
--  >   vdivv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs division between two vectorial control signals at init
-- time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vdivv_i.html>
 
vdivv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vdivv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vdivv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vpowv_i
--  
--  
-- * syntax : 
--  
--  >   vpowv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs power-of operations between two vectorial control
-- signals at init time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vpowv_i.html>
 
vpowv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vpowv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vpowv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vexpv_i
--  
--  
-- * syntax : 
--  
--  >   vexpv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
--  
--  
-- * description : 
--  
--  Performs exponential operations between two vectorial control
-- signals at init time.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vexpv_i.html>
 
vexpv_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vexpv_i i0init i1fn1 i2fn2 i3elements = outOpcode "vexpv_i" args
  where args = [to i1fn1, to i2fn2, to i3elements] ++ map to i0init


-- | * opcode : vcopy_i
--  
--  
-- * syntax : 
--  
--  >   vcopy_i ifn, ifn2, ielements [,idstoffset, isrcoffset]
--  
--  
-- * description : 
--  
--  Copies a vector from one table to another.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vcopy_i.html>
 
vcopy_i :: [Irate] -> Irate -> Irate -> Irate -> SignalOut
vcopy_i i0init i1fn i2fn2 i3elements = outOpcode "vcopy_i" args
  where args = [to i1fn, to i2fn2, to i3elements] ++ map to i0init