-- | Convolution and Morphing module CsoundExpr.Opcodes.Sigmod.SigProcConmorph (convolve, cross2, dconv, ftconv, ftmorf, pconvolve) where import CsoundExpr.Base.Types import CsoundExpr.Base.MultiOut import CsoundExpr.Base.SideEffect import CsoundExpr.Base.UserDefined -- | * opcode : convolve -- -- -- * syntax : -- -- > ar1 [, ar2] [, ar3] [, ar4] convolve ain, ifilcod [, ichannel] -- -- -- * description : -- -- Output is the convolution of signal ain and the impulse response -- contained in ifilcod. If more than one output signal is supplied, -- each will be convolved with the same impulse response. Note that -- it is considerably more efficient to use one instance of the -- operator when processing a mono input to create stereo, or quad, -- outputs. -- -- -- * url : convolve :: [Irate] -> Arate -> String -> MultiOut convolve i0init a1in s2file = opcode "convolve" args where args = [to a1in, to s2file] ++ map to i0init -- | * opcode : cross2 -- -- -- * syntax : -- -- > ares cross2 ain1, ain2, isize, ioverlap, iwin, kbias -- -- -- * description : -- -- This is an implementation of cross synthesis using FFT's. -- -- -- * url : cross2 :: (K k0) => Arate -> Arate -> Irate -> Irate -> Irate -> k0 -> Arate cross2 a0in1 a1in2 i2size i3overlap i4win k5bias = opcode "cross2" args where args = [to a0in1, to a1in2, to i2size, to i3overlap, to i4win, to k5bias] -- | * opcode : dconv -- -- -- * syntax : -- -- > ares dconv asig, isize, ifn -- -- -- * description : -- -- A direct convolution opcode. -- -- -- * url : dconv :: Arate -> Irate -> Irate -> Arate dconv a0sig i1size i2fn = opcode "dconv" args where args = [to a0sig, to i1size, to i2fn] -- | * opcode : ftconv -- -- -- * syntax : -- -- > a1[, a2[, a3[,... a8]]] ftconv ain, ift, iplen[, iskipsamples -- > [, iirlen[, iskipinit]]] -- -- -- * description : -- -- Low latency multichannel convolution, using a function table as -- impulse response source. The algorithm is to split the impulse -- response to partitions of length determined by the iplen -- parameter, and delay and mix partitions so that the original, -- full length impulse response is reconstructed without gaps. The -- output delay (latency) is iplen samples, and does not depend on -- the control rate, unlike in the case of other convolve opcodes. -- -- -- * url : ftconv :: [Irate] -> Arate -> Irate -> Irate -> MultiOut ftconv i0init a1in i2ft i3plen = opcode "ftconv" args where args = [to a1in, to i2ft, to i3plen] ++ map to i0init -- | * opcode : ftmorf -- -- -- * syntax : -- -- > ftmorf kftndx, iftfn, iresfn -- -- -- * description : -- -- Uses an index into a table of ftable numbers to morph between -- adjacent tables in the list.This morphed function is written into -- the table referenced by iresfn on every k-cycle. -- -- -- * url : ftmorf :: (K k0) => k0 -> Irate -> Irate -> SignalOut ftmorf k0ftndx i1ftfn i2resfn = outOpcode "ftmorf" args where args = [to k0ftndx, to i1ftfn, to i2resfn] -- | * opcode : pconvolve -- -- -- * syntax : -- -- > ar1 [, ar2] [, ar3] [, ar4] pconvolve ain, ifilcod [, ipartitionsize, ichannel] -- -- -- * description : -- -- Convolution based on a uniformly partitioned overlap-save -- algorithm. Compared to the convolve opcode, pconvolve has these -- benefits: -- -- -- * url : pconvolve :: [Irate] -> Arate -> String -> MultiOut pconvolve i0init a1in s2file = opcode "pconvolve" args where args = [to a1in, to s2file] ++ map to i0init