csound-expression-opcodes-0.0.1: opcodes for the library csound-expression

Safe HaskellNone

Csound.Typed.Opcode.SignalModifiers

Contents

Synopsis

Amplitude Modifiers.

balance :: Sig -> Sig -> SigSource

Adjust one audio signal according to the values of another.

The rms power of asig can be interrogated, set, or adjusted to match that of a comparator signal.

 ares  balance  asig, acomp [, ihp] [, iskip]

csound doc: http://www.csounds.com/manual/html/balance.html

clip :: Sig -> D -> D -> SigSource

Clips a signal to a predefined limit.

Clips an a-rate signal to a predefined limit, in a “soft” manner, using one of three metho

 ares  clip  asig, imeth, ilimit [, iarg]

csound doc: http://www.csounds.com/manual/html/clip.html

compress :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> SigSource

Compress, limit, expand, duck or gate an audio signal.

This unit functions as an audio compressor, limiter, expander, or noise gate, using either soft-knee or hard-knee mapping, and with dynamically variable performance characteristics. It takes two audio input signals, aasig and acsig, the first of which is modified by a running analysis of the second. Both signals can be the same, or the first can be modified by a different controlling signal.

 ar  compress  aasig, acsig, kthresh, kloknee, khiknee, kratio, katt, krel, ilook

csound doc: http://www.csounds.com/manual/html/compress.html

dam :: Sig -> Sig -> D -> D -> D -> D -> SigSource

A dynamic compressor/expander.

This opcode dynamically modifies a gain value applied to the input sound ain by comparing its power level to a given threshold level. The signal will be compressed/expanded with different factors regarding that it is over or under the threshold.

 ares  dam  asig, kthreshold, icomp1, icomp2, irtime, iftime

csound doc: http://www.csounds.com/manual/html/dam.html

gain :: Sig -> Sig -> SigSource

Adjusts the amplitude audio signal according to a root-mean-square value.

 ares  gain  asig, krms [, ihp] [, iskip]

csound doc: http://www.csounds.com/manual/html/gain.html

Convolution and Morphing.

convolve :: Tuple a => Sig -> Str -> aSource

Convolves a signal and an impulse response.

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.

 ar1 [, ar2] [, ar3] [, ar4]  convolve  ain, ifilcod [, ichannel]

csound doc: http://www.csounds.com/manual/html/convolve.html

cross2 :: Sig -> Sig -> D -> D -> D -> Sig -> SigSource

Cross synthesis using FFT's.

This is an implementation of cross synthesis using FFT's.

 ares  cross2  ain1, ain2, isize, ioverlap, iwin, kbias

csound doc: http://www.csounds.com/manual/html/cross2.html

dconv :: Sig -> D -> Tab -> SigSource

A direct convolution opcode.

 ares  dconv  asig, isize, ifn

csound doc: http://www.csounds.com/manual/html/dconv.html

ftconv :: Tuple a => Sig -> D -> D -> aSource

Low latency multichannel convolution, using a function table as impulse response source.

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.

 a1[, a2[, a3[, ... a8]]]  ftconv  ain, ift, iplen[, iskipsamples \
           [, iirlen[, iskipinit]]]

csound doc: http://www.csounds.com/manual/html/ftconv.html

ftmorf :: Sig -> Tab -> Tab -> SE ()Source

Morphs between multiple ftables as specified in a list.

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.

  ftmorf  kftndx, iftfn, iresfn

csound doc: http://www.csounds.com/manual/html/ftmorf.html

pconvolve :: Tuple a => Sig -> Str -> aSource

Convolution based on a uniformly partitioned overlap-save algorithm

Convolution based on a uniformly partitioned overlap-save algorithm. Compared to the convolve opcode, pconvolve has these benefits:

 ar1 [, ar2] [, ar3] [, ar4]  pconvolve  ain, ifilcod [, ipartitionsize, ichannel]

csound doc: http://www.csounds.com/manual/html/pconvolve.html

Delay.

delay :: Sig -> D -> SigSource

Delays an input signal by some time interval.

A signal can be read from or written into a delay path, or it can be automatically delayed by some time interval.

 ares  delay  asig, idlt [, iskip]

csound doc: http://www.csounds.com/manual/html/delay.html

delay1 :: Sig -> SigSource

Delays an input signal by one sample.

 ares  delay1  asig [, iskip]

csound doc: http://www.csounds.com/manual/html/delay1.html

delayk :: Sig -> D -> SigSource

Delays an input signal by some time interval.

k-rate delay opcodes

 kr  delayk   ksig, idel[, imode]

csound doc: http://www.csounds.com/manual/html/delayk.html

vdel_k :: Sig -> Sig -> D -> SigSource

Delays an input signal by some time interval.

k-rate delay opcodes

 kr  vdel_k   ksig, kdel, imdel[, imode]

csound doc: http://www.csounds.com/manual/html/delayk.html

delayr :: D -> SE SigSource

Reads from an automatically established digital delay line.

 ares  delayr  idlt [, iskip]

csound doc: http://www.csounds.com/manual/html/delayr.html

delayw :: Sig -> SE ()Source

Writes the audio signal to a digital delay line.

  delayw  asig

csound doc: http://www.csounds.com/manual/html/delayw.html

deltap :: Sig -> SE SigSource

Taps a delay line at variable offset times.

Tap a delay line at variable offset times.

 ares  deltap  kdlt

csound doc: http://www.csounds.com/manual/html/deltap.html

deltap3 :: Sig -> SE SigSource

Taps a delay line at variable offset times, uses cubic interpolation.

 ares  deltap3  xdlt

csound doc: http://www.csounds.com/manual/html/deltap3.html

deltapi :: Sig -> SE SigSource

Taps a delay line at variable offset times, uses interpolation.

 ares  deltapi  xdlt

csound doc: http://www.csounds.com/manual/html/deltapi.html

deltapn :: Sig -> SigSource

Taps a delay line at variable offset times.

Tap a delay line at variable offset times.

 ares  deltapn  xnumsamps

csound doc: http://www.csounds.com/manual/html/deltapn.html

deltapx :: Sig -> D -> SE SigSource

Read from or write to a delay line with interpolation.

deltapx is similar to deltapi or deltap3. However, it allows higher quality interpolation. This opcode can read from and write to a delayr/delayw delay line with interpolation.

 aout  deltapx  adel, iwsize

csound doc: http://www.csounds.com/manual/html/deltapx.html

deltapxw :: Sig -> Sig -> D -> SE ()Source

Mixes the input signal to a delay line.

deltapxw mixes the input signal to a delay line. This opcode can be mixed with reading units (deltap, deltapn, deltapi, deltap3, and deltapx) in any order; the actual delay time is the difference of the read and write time. This opcode can read from and write to a delayr/delayw delay line with interpolation.

  deltapxw  ain, adel, iwsize

csound doc: http://www.csounds.com/manual/html/deltapxw.html

multitap :: Sig -> [D] -> SigSource

Multitap delay line implementation.

 ares  multitap  asig [, itime1, igain1] [, itime2, igain2] [...]

csound doc: http://www.csounds.com/manual/html/multitap.html

vdelay :: Sig -> Sig -> D -> SigSource

An interpolating variable time delay.

This is an interpolating variable time delay, it is not very different from the existing implementation (deltapi), it is only easier to use.

 ares  vdelay  asig, adel, imaxdel [, iskip]

csound doc: http://www.csounds.com/manual/html/vdelay.html

vdelay3 :: Sig -> Sig -> D -> SigSource

A variable time delay with cubic interpolation.

vdelay3 is experimental. It is the same as vdelay except that it uses cubic interpolation. (New in Version 3.50.)

 ares  vdelay3  asig, adel, imaxdel [, iskip]

csound doc: http://www.csounds.com/manual/html/vdelay3.html

vdelayx :: Sig -> Sig -> D -> D -> SigSource

A variable delay opcode with high quality interpolation.

 aout  vdelayx  ain, adl, imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayx.html

vdelayxq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig)Source

A 4-channel variable delay opcode with high quality interpolation.

 aout1, aout2, aout3, aout4  vdelayxq  ain1, ain2, ain3, ain4, adl, imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayxq.html

vdelayxs :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)Source

A stereo variable delay opcode with high quality interpolation.

 aout1, aout2  vdelayxs  ain1, ain2, adl, imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayxs.html

vdelayxw :: Sig -> Sig -> D -> D -> SigSource

Variable delay opcodes with high quality interpolation.

 aout  vdelayxw  ain, adl, imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayxw.html

vdelayxwq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig)Source

Variable delay opcodes with high quality interpolation.

 aout1, aout2, aout3, aout4  vdelayxwq  ain1, ain2, ain3, ain4, adl, \
           imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayxwq.html

vdelayxws :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)Source

Variable delay opcodes with high quality interpolation.

 aout1, aout2  vdelayxws  ain1, ain2, adl, imd, iws [, ist]

csound doc: http://www.csounds.com/manual/html/vdelayxws.html

Panning and Spatialization.

bformdec :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> aSource

Deprecated. Decodes an ambisonic B format signal.

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.

 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]]]

csound doc: http://www.csounds.com/manual/html/bformdec.html

bformdec1 :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> aSource

Decodes an ambisonic B format signal

Decodes an ambisonic B format signal into loudspeaker specific signals.

 ao1, ao2  bformdec1  isetup, aw, ax, ay, az [, ar, as, at, au, av \
           [, abk, al, am, an, ao, ap, aq]]
 ao1, ao2, ao3, ao4  bformdec1  isetup, aw, ax, ay, az [, ar, as, at, \
           au, av [, abk, al, am, an, ao, ap, aq]]
 ao1, ao2, ao3, ao4, ao5  bformdec1  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  bformdec1  isetup, aw, ax, ay, az \
           [, ar, as, at, au, av [, abk, al, am, an, ao, ap, aq]]]

csound doc: http://www.csounds.com/manual/html/bformdec1.html

bformenc :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> aSource

Deprecated. Codes a signal into the ambisonic B format.

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.

 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

csound doc: http://www.csounds.com/manual/html/bformenc.html

bformenc1 :: Tuple a => Sig -> Sig -> Sig -> aSource

Codes a signal into the ambisonic B format.

Codes a signal into the ambisonic B format

 aw, ax, ay, az  bformenc1  asig, kalpha, kbeta
 aw, ax, ay, az, ar, as, at, au, av  bformenc1  asig, kalpha, kbeta
 aw, ax, ay, az, ar, as, at, au, av, ak, al, am, an, ao, ap, aq  bformenc1  \
           asig, kalpha, kbeta

csound doc: http://www.csounds.com/manual/html/bformenc1.html

hrtfearly :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> aSource

Generates 3D binaural audio with high-fidelity early reflections in a parametric room using a Phase Truncation algorithm.

This opcode essentially nests the hrtfmove opcode in an image model for a user-definable shoebox-shaped room. A default room can be selected, or advanced room parameters can be used. Room surfaces can be controlled with high and low-frequency absorption coefficients and gain factors of a three-band equaliser.

 aleft, aright, irt60low, irt60high, imfp  hrtfearly  asrc, ksrcx, ksrcy, ksrcz, klstnrx, klstnry, klstnrz, \
           ifilel, ifiler, idefroom [,ifade, isr, iorder, ithreed, kheadrot, iroomx, iroomy, iroomz, iwallhigh, \
           iwalllow, iwallgain1, iwallgain2, iwallgain3, ifloorhigh, ifloorlow, ifloorgain1, ifloorgain2, \
           ifloorgain3, iceilinghigh, iceilinglow, iceilinggain1, iceilinggain2, iceilinggain3]

csound doc: http://www.csounds.com/manual/html/hrtfearly.html

hrtfmove :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)Source

Generates dynamic 3d binaural audio for headphones using magnitude interpolation and phase truncation.

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.

 aleft, aright  hrtfmove  asrc, kAz, kElev, ifilel, ifiler [, imode, ifade, isr]

csound doc: http://www.csounds.com/manual/html/hrtfmove.html

hrtfmove2 :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)Source

Generates dynamic 3d binaural audio for headphones using a Woodworth based spherical head model with improved low frequency phase accuracy.

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.

 aleft, aright  hrtfmove2  asrc, kAz, kElev, ifilel, ifiler [,ioverlap, iradius, isr]

csound doc: http://www.csounds.com/manual/html/hrtfmove2.html

hrtfreverb :: Sig -> D -> D -> D -> D -> (Sig, Sig, D)Source

A binaural, dynamic FDN based diffuse-field reverberator. The opcode works independently as an efficient, flexible reverberator.

A frequency-dependent, efficient reverberant field is created based on low and high frequency desired reverb times. The opcode is designed to work with hrtfearly, ideally using its outputs as inputs. However, hrtfreverb can be used as a standalone tool. Stability is enforced.

 aleft, aright, idel  hrtfreverb  asrc, ilowrt60, ihighrt60, ifilel, ifiler [,isr, imfp, iorder]

csound doc: http://www.csounds.com/manual/html/hrtfreverb.html

hrtfstat :: Sig -> D -> D -> D -> D -> (Sig, Sig)Source

Generates static 3d binaural audio for headphones using a Woodworth based spherical head model with improved low frequency phase accuracy.

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,.

 
           aleft, aright  hrtfstat  asrc, iAz, iElev, ifilel, ifiler [,iradius, isr]
         

csound doc: http://www.csounds.com/manual/html/hrtfstat.html

locsend :: (Sig, Sig, Sig, Sig)Source

Distributes the audio signals of a previous locsig opcode.

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!).

 a1, a2  locsend   a1, a2,  a3, a4  locsend  

csound doc: http://www.csounds.com/manual/html/locsend.html

locsig :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)Source

Takes an input signal and distributes between 2 or 4 channels.

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.

 a1, a2  locsig  asig, kdegree, kdistance, kreverbsend
 a1, a2,  a3, a4  locsig  asig, kdegree, kdistance, kreverbsend

csound doc: http://www.csounds.com/manual/html/locsig.html

pan :: Sig -> Sig -> Sig -> Tab -> (Sig, Sig, Sig, Sig)Source

Distribute an audio signal amongst four channels.

Distribute an audio signal amongst four channels with localization control.

 a1, a2, a3, a4  pan  asig, kx, ky, ifn [, imode] [, ioffset]

csound doc: http://www.csounds.com/manual/html/pan.html

pan2 :: Sig -> Sig -> (Sig, Sig)Source

Distribute an audio signal across two channels.

Distribute an audio signal across two channels with a choice of methods.

 a1, a2  pan2  asig, xp [, imode]

csound doc: http://www.csounds.com/manual/html/pan2.html

space :: Sig -> Tab -> Sig -> Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)Source

Distributes an input signal among 4 channels using cartesian coordinates.

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:

 a1, a2, a3, a4   space  asig, ifn, ktime, kreverbsend, kx, ky

csound doc: http://www.csounds.com/manual/html/space.html

spat3d :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig)Source

Positions the input sound in a 3D space and allows moving the sound at k-rate.

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).

 aW, aX, aY, aZ  spat3d  ain, kX, kY, kZ, idist, ift, imode, imdel, iovr [, istor]

csound doc: http://www.csounds.com/manual/html/spat3d.html

spat3di :: Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig)Source

Positions the input sound in a 3D space with the sound source position set at i-time.

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.

 aW, aX, aY, aZ  spat3di  ain, iX, iY, iZ, idist, ift, imode [, istor]

csound doc: http://www.csounds.com/manual/html/spat3di.html

spat3dt :: D -> D -> D -> D -> D -> D -> D -> D -> SE ()Source

Can be used to render an impulse response for a 3D space at i-time.

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.

  spat3dt  ioutft, iX, iY, iZ, idist, ift, imode, irlen [, iftnocl]

csound doc: http://www.csounds.com/manual/html/spat3dt.html

spdist :: Tab -> Sig -> Sig -> Sig -> SigSource

Calculates distance values from xy coordinates.

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.

 k1  spdist  ifn, ktime, kx, ky

csound doc: http://www.csounds.com/manual/html/spdist.html

spsend :: (Sig, Sig, Sig, Sig)Source

Generates output signals based on a previously defined space opcode.

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).

 a1, a2, a3, a4  spsend  

csound doc: http://www.csounds.com/manual/html/spsend.html

vbap :: Tuple a => Sig -> Sig -> aSource

Distributes an audio signal among many channels.

Distributes an audio signal amongmany channels, up to 64.

 ar1[, ar2...]  vbap  asig, kazim [,
         kelev] [, kspread] [, ilayout]

csound doc: http://www.csounds.com/manual/html/vbap.html

vbap16 :: Tuple a => Sig -> Sig -> aSource

Distributes an audio signal among 16 channels.

 ar1, ..., ar16  vbap16  asig, kazim [, kelev] [, kspread]

csound doc: http://www.csounds.com/manual/html/vbap16.html

vbap16move :: Tuple a => Sig -> D -> D -> D -> [D] -> aSource

Distribute an audio signal among 16 channels with moving virtual sources.

 ar1, ..., ar16  vbap16move  asig, idur, ispread, ifldnum, ifld1 \
           [, ifld2] [...]

csound doc: http://www.csounds.com/manual/html/vbap16move.html

vbap4 :: Sig -> Sig -> (Sig, Sig, Sig, Sig)Source

Distributes an audio signal among 4 channels.

 ar1, ar2, ar3, ar4  vbap4  asig, kazim [, kelev] [, kspread]

csound doc: http://www.csounds.com/manual/html/vbap4.html

vbap4move :: Tuple a => Sig -> D -> D -> D -> [D] -> aSource

Distributes an audio signal among 4 channels with moving virtual sources.

 ar1, ar2, ar3, ar4  vbap4move  asig, idur, ispread, ifldnum, ifld1 \
           [, ifld2] [...]

csound doc: http://www.csounds.com/manual/html/vbap4move.html

vbap8 :: Tuple a => Sig -> Sig -> aSource

Distributes an audio signal among 8 channels.

 ar1, ..., ar8  vbap8  asig, kazim [, kelev] [, kspread]

csound doc: http://www.csounds.com/manual/html/vbap8.html

vbap8move :: Tuple a => Sig -> D -> D -> D -> [D] -> aSource

Distributes an audio signal among 8 channels with moving virtual sources.

 ar1, ..., ar8  vbap8move  asig, idur, ispread, ifldnum, ifld1 \
           [, ifld2] [...]

csound doc: http://www.csounds.com/manual/html/vbap8move.html

vbapg :: Tuple a => Sig -> aSource

Calculates the gains for a sound location between multiple channels.

Calculates the gains for a sound location for up to 64.

 k1[, k2...]  vbapg  kazim [,kelev] [, kspread] [, ilayout]

csound doc: http://www.csounds.com/manual/html/vbapg.html

vbaplsinit :: D -> D -> SE ()Source

Configures VBAP output according to loudspeaker parameters.

  vbaplsinit  idim, ilsnum [, idir1] [, idir2] [...] [, idir32]

csound doc: http://www.csounds.com/manual/html/vbaplsinit.html

vbapmove :: Tuple a => Sig -> D -> D -> D -> [D] -> aSource

Distributes an audio signal among many channels with moving virtual sources.

Distributes an audio signal among upto 64 channels with moving virtual sources.

 ar1[, ar2...]  vbapmove  asig, idur, ispread, ifldnum, ifld1 \
           [, ifld2] [...]

csound doc: http://www.csounds.com/manual/html/vbapmove.html

vbapz :: D -> D -> Sig -> Sig -> SE ()Source

Writes a multi-channel audio signal to a ZAK array.

  vbapz  inumchnls, istartndx, asig, kazim [, kelev] [, kspread]

csound doc: http://www.csounds.com/manual/html/vbapz.html

vbapzmove :: Sig -> D -> D -> D -> [D] -> SE ()Source

Writes a multi-channel audio signal to a ZAK array with moving virtual sources.

  vbapzmove  inumchnls, istartndx, asig, idur, ispread, ifldnum, ifld1, \
           ifld2, [...]

csound doc: http://www.csounds.com/manual/html/vbapzmove.html

Reverberation.

alpass :: Sig -> Sig -> D -> SigSource

Reverberates an input signal with a flat frequency response.

 ares  alpass  asig, krvt, ilpt [, iskip] [, insmps]

csound doc: http://www.csounds.com/manual/html/alpass.html

babo :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> (Sig, Sig)Source

A physical model reverberator.

babo stands for ball-within-the-box. It is a physical model reverberator based on the paper by Davide Rocchesso The Ball within the Box: a sound-processing metaphor, Computer Music Journal, Vol 19, N.4, pp.45-47, Winter 1995.

 a1, a2  babo  asig, ksrcx, ksrcy, ksrcz, irx, iry, irz [, idiff] [, ifno]

csound doc: http://www.csounds.com/manual/html/babo.html

comb :: Sig -> Sig -> D -> SigSource

Reverberates an input signal with a “colored” frequency respon

 ares  comb  asig, krvt, ilpt [, iskip] [, insmps]

csound doc: http://www.csounds.com/manual/html/comb.html

combinv :: Sig -> Sig -> D -> SigSource

Reverberates an input signal with a “colored” frequency respon

Reverberates an input signal with a “colored frequency response with a FIR filter.

 ares  combinv  asig, krvt, ilpt [, iskip] [, insmps]

csound doc: http://www.csounds.com/manual/html/combinv.html

freeverb :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig)Source

Opcode version of Jezar's Freeverb

freeverb is a stereo reverb unit based on Jezar's public domain C++ sources, composed of eight parallel comb filters on both channels, followed by four allpass units in series. The filters on the right channel are slightly detuned compared to the left channel in order to create a stereo effect.

 aoutL, aoutR  freeverb  ainL, ainR, kRoomSize, kHFDamp[, iSRate[, iSkip]] 

csound doc: http://www.csounds.com/manual/html/freeverb.html

nestedap :: Sig -> D -> D -> D -> D -> SigSource

Three different nested all-pass filters.

Three different nested all-pass filters, useful for implementing reverbs.

 ares  nestedap  asig, imode, imaxdel, idel1, igain1 [, idel2] [, igain2] \
           [, idel3] [, igain3] [, istor]

csound doc: http://www.csounds.com/manual/html/nestedap.html

nreverb :: Sig -> Sig -> Sig -> SigSource

A reverberator consisting of 6 parallel comb-lowpass filters.

This is a reverberator consisting of 6 parallel comb-lowpass filters being fed into a series of 5 allpass filters. nreverb replaces reverb2 (version 3.48) and so both opcodes are identical.

 ares  nreverb  asig, ktime, khdif [, iskip] [,inumCombs] [, ifnCombs] \
           [, inumAlpas] [, ifnAlpas]

csound doc: http://www.csounds.com/manual/html/nreverb.html

platerev :: Tuple a => D -> D -> Sig -> D -> D -> D -> D -> [Sig] -> aSource

Models the reverberation of a metal plate.

Models the reverberation of a rectangular metal plate with settable physical characteristics when excited by audio signal(s).

 a1[, a2, ...]  platerev  itabexcite. itabouts, kbndry, iaspect, istiff, idecay, iloss, aexcite1[, aexcite2, ...]

csound doc: http://www.csounds.com/manual/html/platerev.html

reverb :: Sig -> Sig -> SigSource

Reverberates an input signal with a “natural room” frequency respon

 ares  reverb  asig, krvt [, iskip]

csound doc: http://www.csounds.com/manual/html/reverb.html

reverb2 :: Sig -> Sig -> Sig -> SigSource

Same as the nreverb opcode.

 ares  reverb2  asig, ktime, khdif [, iskip] [,inumCombs] \
           [, ifnCombs] [, inumAlpas] [, ifnAlpas]

csound doc: http://www.csounds.com/manual/html/reverb2.html

reverbsc :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig)Source

8 delay line stereo FDN reverb, based on work by Sean Costello

8 delay line stereo FDN reverb, with feedback matrix based upon physical modeling scattering junction of 8 lossless waveguides of equal characteristic impedance. Based on Csound orchestra version by Sean Costello.

 aoutL, aoutR  reverbsc  ainL, ainR, kfblvl, kfco[, israte[, ipitchm[, iskip]]] 

csound doc: http://www.csounds.com/manual/html/reverbsc.html

valpass :: Sig -> Sig -> Sig -> D -> SigSource

Variably reverberates an input signal with a flat frequency response.

 ares  valpass  asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]

csound doc: http://www.csounds.com/manual/html/valpass.html

vcomb :: Sig -> Sig -> Sig -> D -> SigSource

Variably reverberates an input signal with a “colored” frequency respon

 ares  vcomb  asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]

csound doc: http://www.csounds.com/manual/html/vcomb.html

Sample Level Operators.

denorm :: [Sig] -> SE ()Source

Mixes low level noise to a list of a-rate signals

Mixes low level (~1e-20 for floats, and ~1e-56 for doubles) noise to a list of a-rate signals. Can be used before IIR filters and reverbs to avoid denormalized numbers which may otherwise result in significantly increased CPU usage.

  denorm  a1[, a2[, a3[, ... ]]]

csound doc: http://www.csounds.com/manual/html/denorm.html

diff :: Sig -> SigSource

Modify a signal by differentiation.

 ares  diff  asig [, iskip]
 kres  diff  ksig [, iskip]

csound doc: http://www.csounds.com/manual/html/diff.html

downsamp :: Sig -> SigSource

Modify a signal by down-sampling.

 kres  downsamp  asig [, iwlen]

csound doc: http://www.csounds.com/manual/html/downsamp.html

fold :: Sig -> Sig -> SigSource

Adds artificial foldover to an audio signal.

 ares  fold  asig, kincr

csound doc: http://www.csounds.com/manual/html/fold.html

integ :: Sig -> SigSource

Modify a signal by integration.

 ares  integ  asig [, iskip]
 kres  integ  ksig [, iskip]

csound doc: http://www.csounds.com/manual/html/integ.html

interp :: Sig -> SigSource

Converts a control signal to an audio signal using linear interpolation.

 ares  interp  ksig [, iskip] [, imode]

csound doc: http://www.csounds.com/manual/html/interp.html

ntrpol :: Sig -> Sig -> Sig -> SigSource

Calculates the weighted mean value of two input signals.

Calculates the weighted mean value (i.e. linear interpolation) of two input signals

 ares  ntrpol  asig1, asig2, kpoint [, imin] [, imax]
 ires  ntrpol  isig1, isig2, ipoint [, imin] [, imax]
 kres  ntrpol  ksig1, ksig2, kpoint [, imin] [, imax]

csound doc: http://www.csounds.com/manual/html/ntrpol.html

samphold :: Sig -> Sig -> SigSource

Performs a sample-and-hold operation on its input.

 ares  samphold  asig, agate [, ival] [, ivstor]
 kres  samphold  ksig, kgate [, ival] [, ivstor]

csound doc: http://www.csounds.com/manual/html/samphold.html

upsamp :: Sig -> SigSource

Modify a signal by up-sampling.

 ares  upsamp  ksig

csound doc: http://www.csounds.com/manual/html/upsamp.html

vaget :: Sig -> Sig -> SigSource

Access values of the current buffer of an a-rate variable by indexing.

Access values of the current buffer of an a-rate variable by indexing. Useful for doing sample-by-sample manipulation at k-rate without using setksmps 1.

 kval  vaget  kndx, avar

csound doc: http://www.csounds.com/manual/html/vaget.html

vaset :: Sig -> Sig -> Sig -> SE ()Source

Write value of into the current buffer of an a-rate variable by index.

Write values into the current buffer of an a-rate variable at the given index. Useful for doing sample-by-sample manipulation at k-rate without using setksmps 1.

  vaset  kval, kndx, avar

csound doc: http://www.csounds.com/manual/html/vaset.html

Signal Limiters.

limit :: Sig -> Sig -> Sig -> SigSource

Sets the lower and upper limits of the value it processes.

 ares  limit  asig, klow, khigh
 ires  limit  isig, ilow, ihigh
 kres  limit  ksig, klow, khigh

csound doc: http://www.csounds.com/manual/html/limit.html

mirror :: Sig -> Sig -> Sig -> SigSource

Reflects the signal that exceeds the low and high thresholds.

 ares  mirror  asig, klow, khigh
 ires  mirror  isig, ilow, ihigh
 kres  mirror  ksig, klow, khigh

csound doc: http://www.csounds.com/manual/html/mirror.html

wrap :: Sig -> Sig -> Sig -> SigSource

Wraps-around the signal that exceeds the low and high thresholds.

 ares  wrap  asig, klow, khigh
 ires  wrap  isig, ilow, ihigh
 kres  wrap  ksig, klow, khigh

csound doc: http://www.csounds.com/manual/html/wrap.html

Special Effects.

distort :: Sig -> Sig -> Tab -> SigSource

Distort an audio signal via waveshaping and optional clipping.

 ar  distort  asig, kdist, ifn[, ihp, istor]

csound doc: http://www.csounds.com/manual/html/distort.html

distort1 :: Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Modified hyperbolic tangent distortion.

Implementation of modified hyperbolic tangent distortion. distort1 can be used to generate wave shaping distortion based on a modification of the tanh function.

 ares  distort1  asig, kpregain, kpostgain, kshape1, kshape2[, imode]

csound doc: http://www.csounds.com/manual/html/distort1.html

flanger :: Sig -> Sig -> Sig -> SigSource

A user controlled flanger.

 ares  flanger  asig, adel, kfeedback [, imaxd]

csound doc: http://www.csounds.com/manual/html/flanger.html

harmon :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> SigSource

Analyze an audio input and generate harmonizing voices in synchrony.

 ares  harmon  asig, kestfrq, kmaxvar, kgenfreq1, kgenfreq2, imode, \
           iminfrq, iprd

csound doc: http://www.csounds.com/manual/html/harmon.html

harmon2 :: Sig -> Sig -> Sig -> Sig -> D -> D -> SigSource

Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.

Generate harmonizing voices with formants preserved.

 ares  harmon2  asig, koct, kfrq1, kfrq2, icpsmode, ilowest[, ipolarity]

csound doc: http://www.csounds.com/manual/html/harmon2.html

harmon3 :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> SigSource

Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.

Generate harmonizing voices with formants preserved.

 ares  harmon3  asig, koct, kfrq1, \
         kfrq2, kfrq3, icpsmode, ilowest[, ipolarity]

csound doc: http://www.csounds.com/manual/html/harmon2.html

harmon4 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> SigSource

Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.

Generate harmonizing voices with formants preserved.

 ares  harmon4  asig, koct, kfrq1, \
         kfrq2, kfrq3, kfrq4, icpsmode, ilowest[, ipolarity]

csound doc: http://www.csounds.com/manual/html/harmon2.html

phaser1 :: Sig -> Sig -> Sig -> Sig -> SigSource

First-order allpass filters arranged in a series.

An implementation of iord number of first-order allpass filters in series.

 ares  phaser1  asig, kfreq, kord, kfeedback [, iskip]

csound doc: http://www.csounds.com/manual/html/phaser1.html

phaser2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Second-order allpass filters arranged in a series.

An implementation of iord number of second-order allpass filters in series.

 ares  phaser2  asig, kfreq, kq, kord, kmode, ksep, kfeedback

csound doc: http://www.csounds.com/manual/html/phaser2.html

Standard Filters.

atone :: Sig -> Sig -> SigSource

A hi-pass filter whose transfer functions are the complements of the tone opcode.

 ares  atone  asig, khp [, iskip]

csound doc: http://www.csounds.com/manual/html/atone.html

atonex :: Sig -> Sig -> SigSource

Emulates a stack of filters using the atone opcode.

atonex is equivalent to a filter consisting of more layers of atone with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.

 ares  atonex  asig, khp [, inumlayer] [, iskip]

csound doc: http://www.csounds.com/manual/html/atonex.html

biquad :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

A sweepable general purpose biquadratic digital filter.

 ares  biquad  asig, kb0, kb1, kb2, ka0, ka1, ka2 [, iskip]

csound doc: http://www.csounds.com/manual/html/biquad.html

biquada :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

A sweepable general purpose biquadratic digital filter with a-rate parameters.

A sweepable general purpose biquadratic digital filter.

 ares  biquada  asig, ab0, ab1, ab2, aa0, aa1, aa2 [, iskip]

csound doc: http://www.csounds.com/manual/html/biquada.html

butbp :: Sig -> Sig -> Sig -> SigSource

Same as the butterbp opcode.

 ares  butbp  asig, kfreq, kband [, iskip]

csound doc: http://www.csounds.com/manual/html/butbp.html

butbr :: Sig -> Sig -> Sig -> SigSource

Same as the butterbr opcode.

 ares  butbr  asig, kfreq, kband [, iskip]

csound doc: http://www.csounds.com/manual/html/butbr.html

buthp :: Sig -> Sig -> SigSource

Same as the butterhp opcode.

 ares  buthp  asig, kfreq [, iskip]

csound doc: http://www.csounds.com/manual/html/buthp.html

butlp :: Sig -> Sig -> SigSource

Same as the butterlp opcode.

 ares  butlp  asig, kfreq [, iskip]

csound doc: http://www.csounds.com/manual/html/butlp.html

butterbp :: Sig -> Sig -> Sig -> SigSource

A band-pass Butterworth filter.

Implementation of a second-order band-pass Butterworth filter. This opcode can also be written as butbp.

 ares  butterbp  asig, kfreq, kband [, iskip]

csound doc: http://www.csounds.com/manual/html/butterbp.html

butterbr :: Sig -> Sig -> Sig -> SigSource

A band-reject Butterworth filter.

Implementation of a second-order band-reject Butterworth filter. This opcode can also be written as butbr.

 ares  butterbr  asig, kfreq, kband [, iskip]

csound doc: http://www.csounds.com/manual/html/butterbr.html

butterhp :: Sig -> Sig -> SigSource

A high-pass Butterworth filter.

Implementation of second-order high-pass Butterworth filter. This opcode can also be written as buthp.

 ares  butterhp  asig, kfreq [, iskip]

csound doc: http://www.csounds.com/manual/html/butterhp.html

butterlp :: Sig -> Sig -> SigSource

A low-pass Butterworth filter.

Implementation of a second-order low-pass Butterworth filter. This opcode can also be written as butlp.

 ares  butterlp  asig, kfreq [, iskip]

csound doc: http://www.csounds.com/manual/html/butterlp.html

clfilt :: Sig -> Sig -> D -> D -> SigSource

Implements low-pass and high-pass filters of different styles.

Implements the classical standard analog filter types: low-pass and high-pass. They are implemented with the four classical kinds of filters: Butterworth, Chebyshev Type I, Chebyshev Type II, and Elliptical. The number of poles may be any even number from 2 to 80.

 ares  clfilt  asig, kfreq, itype, inpol [, ikind] [, ipbr] [, isba] [, iskip]

csound doc: http://www.csounds.com/manual/html/clfilt.html

doppler :: Sig -> Sig -> Sig -> SigSource

A fast and robust method for approximating sound propagation, achieving convincing Doppler shifts without having to solve equations.

A fast and robust method for approximating sound propagation, achieving convincing Doppler shifts without having to solve equations. The method computes frequency shifts based on reading an input delay line at a delay time computed from the distance between source and mic and the speed of sound. One instance of the opcode is required for each dimension of space through which the sound source moves. If the source sound moves at a constant speed from in front of the microphone, through the microphone, to behind the microphone, then the output will be frequency shifted above the source frequency at a constant frequency while the source approaches, then discontinuously will be shifted below the source frequency at a constant frequency as the source recedes from the microphone. If the source sound moves at a constant speed through a point to one side of the microphone, then the rate of change of position will not be constant, and the familiar Doppler frequency shift typical of a siren or engine approaching and receding along a road beside a listener will be heard.

 ashifted  doppler  asource, ksourceposition, kmicposition [, isoundspeed, ifiltercutoff]

csound doc: http://www.csounds.com/manual/html/doppler.html

mode :: Sig -> Sig -> Sig -> SigSource

A filter that simulates a mass-spring-damper system

Filters the incoming signal with the specified resonance frequency and quality factor. It can also be seen as a signal generator for high quality factor, with an impulse for the excitation. You can combine several modes to built complex instruments such as bells or guitar tables.

 aout  mode  ain, kfreq, kQ [, iskip]

csound doc: http://www.csounds.com/manual/html/mode.html

tone :: Sig -> Sig -> SigSource

A first-order recursive low-pass filter with variable frequency response.

 ares  tone  asig, khp [, iskip]

csound doc: http://www.csounds.com/manual/html/tone.html

tonex :: Sig -> Sig -> SigSource

Emulates a stack of filters using the tone opcode.

tonex is equivalent to a filter consisting of more layers of tone with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.

 ares  tonex   asig, khp [, inumlayer] [, iskip]

csound doc: http://www.csounds.com/manual/html/tonex.html

Standard Filters:Resonant.

areson :: Sig -> Sig -> Sig -> SigSource

A notch filter whose transfer functions are the complements of the reson opcode.

 ares  areson  asig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/areson.html

bqrez :: Sig -> Sig -> Sig -> SigSource

A second-order multi-mode filter.

 ares  bqrez  asig, xfco, xres [, imode] [, iskip]

csound doc: http://www.csounds.com/manual/html/bqrez.html

lowpass2 :: Sig -> Sig -> Sig -> SigSource

A resonant lowpass filter.

Implementation of a resonant second-order lowpass filter.

 ares  lowpass2  asig, kcf, kq [, iskip]

csound doc: http://www.csounds.com/manual/html/lowpass2.html

lowres :: Sig -> Sig -> Sig -> SigSource

Another resonant lowpass filter.

lowres is a resonant lowpass filter.

 ares  lowres  asig, kcutoff, kresonance [, iskip]

csound doc: http://www.csounds.com/manual/html/lowres.html

lowresx :: Sig -> Sig -> Sig -> SigSource

Simulates layers of serially connected resonant lowpass filters.

lowresx is equivalent to more layers of lowres with the same arguments serially connected.

 ares  lowresx  asig, kcutoff, kresonance [, inumlayer] [, iskip]

csound doc: http://www.csounds.com/manual/html/lowresx.html

lpf18 :: Sig -> Sig -> Sig -> Sig -> SigSource

A 3-pole sweepable resonant lowpass filter.

Implementation of a 3 pole sweepable resonant lowpass filter.

 ares  lpf18  asig, kfco, kres, kdist [, iskip]

csound doc: http://www.csounds.com/manual/html/lpf18.html

moogladder :: Sig -> Sig -> Sig -> SigSource

Moog ladder lowpass filter.

Moogladder is an new digital implementation of the Moog ladder filter based on the work of Antti Huovilainen, described in the paper Non-Linear Digital Implementation of the Moog Ladder Filter (Proceedings of DaFX04, Univ of Napoli). This implementation is probably a more accurate digital representation of the original analogue filter.

 asig  moogladder  ain, kcf, kres[, istor]

csound doc: http://www.csounds.com/manual/html/moogladder.html

moogvcf :: Sig -> Sig -> Sig -> SigSource

A digital emulation of the Moog diode ladder filter configuration.

 ares  moogvcf  asig, xfco, xres [,iscale, iskip]

csound doc: http://www.csounds.com/manual/html/moogvcf.html

moogvcf2 :: Sig -> Sig -> Sig -> SigSource

A digital emulation of the Moog diode ladder filter configuration.

 ares  moogvcf2  asig, xfco, xres [,iscale, iskip]

csound doc: http://www.csounds.com/manual/html/moogvcf2.html

reson :: Sig -> Sig -> Sig -> SigSource

A second-order resonant filter.

 ares  reson  asig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/reson.html

resonr :: Sig -> Sig -> Sig -> SigSource

A bandpass filter with variable frequency response.

Implementations of a second-order, two-pole two-zero bandpass filter with variable frequency response.

 ares  resonr  asig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/resonr.html

resonx :: Sig -> Sig -> Sig -> SigSource

Emulates a stack of filters using the reson opcode.

resonx is equivalent to a filters consisting of more layers of reson with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.

 ares  resonx  asig, kcf, kbw [, inumlayer] [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/resonx.html

resony :: Sig -> Sig -> Sig -> D -> Sig -> SigSource

A bank of second-order bandpass filters, connected in parallel.

 ares  resony  asig, kbf, kbw, inum, ksep [, isepmode] [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/resony.html

resonz :: Sig -> Sig -> Sig -> SigSource

A bandpass filter with variable frequency response.

Implementations of a second-order, two-pole two-zero bandpass filter with variable frequency response.

 ares  resonz  asig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/resonz.html

rezzy :: Sig -> Sig -> Sig -> SigSource

A resonant low-pass filter.

 ares  rezzy  asig, xfco, xres [, imode, iskip]

csound doc: http://www.csounds.com/manual/html/rezzy.html

statevar :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)Source

State-variable filter.

Statevar is a new digital implementation of the analogue state-variable filter. This filter has four simultaneous outputs: high-pass, low-pass, band-pass and band-reject. This filter uses oversampling for sharper resonance (default: 3 times oversampling). It includes a resonance limiter that prevents the filter from getting unstable.

 ahp,alp,abp,abr  statevar  ain, kcf, kq [, iosamps, istor]

csound doc: http://www.csounds.com/manual/html/statevar.html

svfilter :: Sig -> Sig -> Sig -> (Sig, Sig, Sig)Source

A resonant second order filter, with simultaneous lowpass, highpass and bandpass outputs.

Implementation of a resonant second order filter, with simultaneous lowpass, highpass and bandpass outputs.

 alow, ahigh, aband  svfilter   asig, kcf, kq [, iscl]

csound doc: http://www.csounds.com/manual/html/svfilter.html

tbvcf :: Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Models some of the filter characteristics of a Roland TB303 voltage-controlled filter.

This opcode attempts to model some of the filter characteristics of a Roland TB303 voltage-controlled filter. Euler's method is used to approximate the system, rather than traditional filter methods. Cutoff frequency, Q, and distortion are all coupled. Empirical methods were used to try to unentwine, but frequency is only approximate as a result. Future fixes for some problems with this opcode may break existing orchestras relying on this version of tbvcf.

 ares  tbvcf  asig, xfco, xres, kdist, kasym [, iskip]

csound doc: http://www.csounds.com/manual/html/tbvcf.html

vlowres :: Sig -> Sig -> Sig -> D -> Sig -> SigSource

A bank of filters in which the cutoff frequency can be separated under user control.

A bank of filters in which the cutoff frequency can be separated under user control

 ares  vlowres  asig, kfco, kres, iord, ksep

csound doc: http://www.csounds.com/manual/html/vlowres.html

Standard Filters:Control.

aresonk :: Sig -> Sig -> Sig -> SigSource

A notch filter whose transfer functions are the complements of the reson opcode.

 kres  aresonk  ksig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/aresonk.html

atonek :: Sig -> Sig -> SigSource

A hi-pass filter whose transfer functions are the complements of the tonek opcode.

 kres  atonek  ksig, khp [, iskip]

csound doc: http://www.csounds.com/manual/html/atonek.html

lineto :: Sig -> Sig -> SigSource

Generate glissandos starting from a control signal.

 kres  lineto  ksig, ktime

csound doc: http://www.csounds.com/manual/html/lineto.html

port :: Sig -> D -> SigSource

Applies portamento to a step-valued control signal.

 kres  port  ksig, ihtim [, isig]

csound doc: http://www.csounds.com/manual/html/port.html

portk :: Sig -> Sig -> SigSource

Applies portamento to a step-valued control signal.

 kres  portk  ksig, khtim [, isig]

csound doc: http://www.csounds.com/manual/html/portk.html

resonk :: Sig -> Sig -> Sig -> SigSource

A second-order resonant filter.

 kres  resonk  ksig, kcf, kbw [, iscl] [, iskip]

csound doc: http://www.csounds.com/manual/html/resonk.html

resonxk :: Sig -> Sig -> Sig -> SigSource

Control signal resonant filter stack.

resonxk is equivalent to a group of resonk filters, with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff.

 kres  resonxk  ksig, kcf, kbw[, inumlayer, iscl, istor]

csound doc: http://www.csounds.com/manual/html/resonxk.html

tlineto :: Sig -> Sig -> Sig -> SigSource

Generate glissandos starting from a control signal.

Generate glissandos starting from a control signal with a trigger.

 kres  tlineto  ksig, ktime, ktrig

csound doc: http://www.csounds.com/manual/html/tlineto.html

tonek :: Sig -> Sig -> SigSource

A first-order recursive low-pass filter with variable frequency response.

 kres  tonek  ksig, khp [, iskip]

csound doc: http://www.csounds.com/manual/html/tonek.html

Specialized Filters.

dcblock :: Sig -> SigSource

A DC blocking filter.

Implements the DC blocking filter

 ares  dcblock  ain [, igain]

csound doc: http://www.csounds.com/manual/html/dcblock.html

dcblock2 :: Sig -> SigSource

A DC blocking filter.

Implements a DC blocking filter with improved DC attenuation.

 ares  dcblock2  ain [, iorder] [, iskip]

csound doc: http://www.csounds.com/manual/html/dcblock2.html

eqfil :: Sig -> Sig -> Sig -> Sig -> SigSource

Equalizer filter

The opcode eqfil is a 2nd order tunable equalisation filter based on Regalia and Mitra design (Tunable Digital Frequency Response Equalization Filters, IEEE Trans. on Ac., Sp. and Sig Proc., 35 (1), 1987). It provides a peak/notch filter for building parametric/graphic equalisers.

 asig  eqfil  ain, kcf, kbw, kgain[, istor]

csound doc: http://www.csounds.com/manual/html/eqfil.html

filter2 :: Sig -> D -> D -> [D] -> SigSource

Performs filtering using a transposed form-II digital filter lattice with no time-varying control.

General purpose custom filter with no time-varying pole control. The filter coefficients implement the following difference equation:

 ares  filter2  asig, iM, iN, ib0, ib1, ..., ibM, ia1, ia2, ..., iaN
 kres  filter2  ksig, iM, iN, ib0, ib1, ..., ibM, ia1, ia2, ..., iaN

csound doc: http://www.csounds.com/manual/html/filter2.html

fofilter :: Sig -> Sig -> Sig -> Sig -> SigSource

Formant filter.

Fofilter generates a stream of overlapping sinewave grains, when fed with a pulse train. Each grain is the impulse response of a combination of two BP filters. The grains are defined by their attack time (determining the skirtwidth of the formant region at -60dB) and decay time (-6dB bandwidth). Overlapping will occur when 1/freq < decay, but, unlike FOF, there is no upper limit on the number of overlaps. The original idea for this opcode came from J McCartney's formlet class in SuperCollider, but this is possibly implemented differently(?).

 asig  fofilter  ain, kcf, kris, kdec[, istor]

csound doc: http://www.csounds.com/manual/html/fofilter.html

hilbert :: Sig -> (Sig, Sig)Source

A Hilbert transformer.

An IIR implementation of a Hilbert transformer.

 ar1, ar2  hilbert  asig

csound doc: http://www.csounds.com/manual/html/hilbert.html

nlfilt :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

A filter with a non-linear effect.

Implements the filter:

 ares  nlfilt  ain, ka, kb, kd, kC, kL

csound doc: http://www.csounds.com/manual/html/nlfilt.html

nlfilt2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

A filter with a non-linear effect and blowup protection.

Implements the filter:

 ares  nlfilt2  ain, ka, kb, kd, kC, kL

csound doc: http://www.csounds.com/manual/html/nlfilt2.html

pareq :: Sig -> Sig -> Sig -> Sig -> SigSource

Implementation of Zoelzer's parametric equalizer filters.

Implementation of Zoelzer's parametric equalizer filters, with some modifications by the author.

 ares  pareq  asig, kc, kv, kq [, imode] [, iskip]

csound doc: http://www.csounds.com/manual/html/pareq.html

rbjeq :: Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Parametric equalizer and filter opcode with 7 filter types, based on algorithm by Robert Bristow-Johnson.

Parametric equalizer and filter opcode with 7 filter types, based on algorithm by Robert Bristow-Johnson.

 ar  rbjeq  asig, kfco, klvl, kQ, kS[, imode]

csound doc: http://www.csounds.com/manual/html/rbjeq.html

zfilter2 :: Sig -> Sig -> Sig -> D -> D -> [D] -> SigSource

Performs filtering using a transposed form-II digital filter lattice with radial pole-shearing and angular pole-warping.

General purpose custom filter with time-varying pole control. The filter coefficients implement the following difference equation:

 ares  zfilter2  asig, kdamp, kfreq, iM, iN, ib0, ib1, ..., ibM, \
           ia1,ia2, ..., iaN

csound doc: http://www.csounds.com/manual/html/zfilter2.html

Waveguides.

wguide1 :: Sig -> Sig -> Sig -> Sig -> SigSource

A simple waveguide model consisting of one delay-line and one first-order lowpass filter.

 ares  wguide1  asig, xfreq, kcutoff, kfeedback

csound doc: http://www.csounds.com/manual/html/wguide1.html

wguide2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

A model of beaten plate consisting of two parallel delay-lines and two first-order lowpass filters.

 ares  wguide2  asig, xfreq1, xfreq2, kcutoff1, kcutoff2, \
           kfeedback1, kfeedback2

csound doc: http://www.csounds.com/manual/html/wguide2.html

Waveshaping.

chebyshevpoly :: Sig -> [Sig] -> SigSource

Efficiently evaluates the sum of Chebyshev polynomials of arbitrary order.

The chebyshevpoly opcode calculates the value of a polynomial expression with a single a-rate input variable that is made up of a linear combination of the first N Chebyshev polynomials of the first kind. Each Chebyshev polynomial, Tn(x), is weighted by a k-rate coefficient, kn, so that the opcode is calculating a sum of any number of terms in the form kn*Tn(x). Thus, the chebyshevpoly opcode allows for the waveshaping of an audio signal with a dynamic transfer function that gives precise control over the harmonic content of the output.

 aout  chebyshevpoly  ain, k0 [, k1 [, k2 [...]]]

csound doc: http://www.csounds.com/manual/html/chebyshevpoly.html

pdclip :: Sig -> Sig -> Sig -> SigSource

Performs linear clipping on an audio signal or a phasor.

The pdclip opcode allows a percentage of the input range of a signal to be clipped to fullscale. It is similar to simply multiplying the signal and limiting the range of the result, but pdclip allows you to think about how much of the signal range is being distorted instead of the scalar factor and has a offset parameter for assymetric clipping of the signal range. pdclip is also useful for remapping phasors for phase distortion synthesis.

 aout  pdclip  ain, kWidth, kCenter [, ibipolar [, ifullscale]]

csound doc: http://www.csounds.com/manual/html/pdclip.html

pdhalf :: Sig -> Sig -> SigSource

Distorts a phasor for reading the two halves of a table at different rates.

The pdhalf opcode is designed to emulate the classic phase distortion synthesis method of the Casio CZ-series of synthesizers from the mid-1980's. This technique reads the first and second halves of a function table at different rates in order to warp the waveform. For example, pdhalf can smoothly transform a sine wave into something approximating the shape of a saw wave.

 aout  pdhalf  ain, kShapeAmount [, ibipolar [, ifullscale]]

csound doc: http://www.csounds.com/manual/html/pdhalf.html

pdhalfy :: Sig -> Sig -> SigSource

Distorts a phasor for reading two unequal portions of a table in equal periods.

The pdhalfy opcode is a variation on the phase distortion synthesis method of the pdhalf opcode. It is useful for distorting a phasor in order to read two unequal portions of a table in the same number of samples.

 aout  pdhalfy  ain, kShapeAmount [, ibipolar [, ifullscale]]

csound doc: http://www.csounds.com/manual/html/pdhalfy.html

powershape :: Sig -> Sig -> SigSource

Waveshapes a signal by raising it to a variable exponent.

The powershape opcode raises an input signal to a power with pre- and post-scaling of the signal so that the output will be in a predictable range. It also processes negative inputs in a symmetrical way to positive inputs, calculating a dynamic transfer function that is useful for waveshaping.

 aout  powershape  ain, kShapeAmount [, ifullscale]

csound doc: http://www.csounds.com/manual/html/powershape.html

Comparators and Accumulators.

max' :: [Sig] -> SigSource

Produces a signal that is the maximum of any number of input signals.

The max opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the maximum of all of the inputs. For a-rate signals, the inputs are compared one sample at a time (i.e. max does not scan an entire ksmps period of a signal for its local maximum as the max_k opcode does).

 amax  max  ain1, ain2 [, ain3] [, ain4] [...]
 kmax  max  kin1, kin2 [, kin3] [, kin4] [...]

csound doc: http://www.csounds.com/manual/html/max.html

max_k :: Sig -> Sig -> D -> SigSource

Local maximum (or minimum) value of an incoming asig signal

max_k outputs the local maximum (or minimum) value of the incoming asig signal, checked in the time interval between ktrig has become true twice.

 knumkout  max_k  asig, ktrig, itype

csound doc: http://www.csounds.com/manual/html/max_k.html

maxabs :: [Sig] -> SigSource

Produces a signal that is the maximum of the absolute values of any number of input signals.

The maxabs opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the maximum of all of the inputs. It is identical to the max opcode except that it takes the absolute value of each input before comparing them. Therefore, the output is always non-negative. For a-rate signals, the inputs are compared one sample at a time (i.e. maxabs does not scan an entire ksmps period of a signal for its local maximum as the max_k opcode does).

 amax  maxabs  ain1, ain2 [, ain3] [, ain4] [...]
 kmax  maxabs  kin1, kin2 [, kin3] [, kin4] [...]

csound doc: http://www.csounds.com/manual/html/maxabs.html

maxabsaccum :: Sig -> Sig -> SE ()Source

Accumulates the maximum of the absolute values of audio signals.

maxabsaccum compares two audio-rate variables and stores the maximum of their absolute values into the first.

  maxabsaccum  aAccumulator, aInput

csound doc: http://www.csounds.com/manual/html/maxabsaccum.html

maxaccum :: Sig -> Sig -> SE ()Source

Accumulates the maximum value of audio signals.

maxaccum compares two audio-rate variables and stores the maximum value between them into the first.

  maxaccum  aAccumulator, aInput

csound doc: http://www.csounds.com/manual/html/maxaccum.html

min' :: [Sig] -> SigSource

Produces a signal that is the minimum of any number of input signals.

The min opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the minimum of all of the inputs. For a-rate signals, the inputs are compared one sample at a time (i.e. min does not scan an entire ksmps period of a signal for its local minimum as the max_k opcode does).

 amin  min  ain1, ain2 [, ain3] [, ain4] [...]
 kmin  min  kin1, kin2 [, kin3] [, kin4] [...]

csound doc: http://www.csounds.com/manual/html/min.html

minabs :: [Sig] -> SigSource

Produces a signal that is the minimum of the absolute values of any number of input signals.

The minabs opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the minimum of all of the inputs. It is identical to the min opcode except that it takes the absolute value of each input before comparing them. Therefore, the output is always non-negative. For a-rate signals, the inputs are compared one sample at a time (i.e. minabs does not scan an entire ksmps period of a signal for its local minimum as the max_k opcode does).

 amin  minabs  ain1, ain2 [, ain3] [, ain4] [...]
 kmin  minabs  kin1, kin2 [, kin3] [, kin4] [...]

csound doc: http://www.csounds.com/manual/html/minabs.html

minabsaccum :: Sig -> Sig -> SE ()Source

Accumulates the minimum of the absolute values of audio signals.

minabsaccum compares two audio-rate variables and stores the minimum of their absolute values into the first.

  minabsaccum  aAccumulator, aInput

csound doc: http://www.csounds.com/manual/html/minabsaccum.html

minaccum :: Sig -> Sig -> SE ()Source

Accumulates the minimum value of audio signals.

minaccum compares two audio-rate variables and stores the minimum value between them into the first.

  minaccum  aAccumulator, aInput

csound doc: http://www.csounds.com/manual/html/minaccum.html