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

Safe HaskellNone
LanguageHaskell98

Csound.Typed.Opcode.SignalGenerators

Contents

Synopsis

Additive Synthesis/Resynthesis.

adsyn :: Sig -> Sig -> Sig -> Str -> Sig Source

Output is an additive set of individually controlled sinusoids, using an oscillator bank.

ares  adsyn  kamod, kfmod, ksmod, ifilcod

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

adsynt :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig Source

Performs additive synthesis with an arbitrary number of partials, not necessarily harmonic.

ares  adsynt  kamp, kcps, iwfn, ifreqfn, iampfn, icnt [, iphs]

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

adsynt2 :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig Source

Performs additive synthesis with an arbitrary number of partials -not necessarily harmonic- with interpolation.

Performs additive synthesis with an arbitrary number of partials, not necessarily harmonic. (see adsynt for detailed manual)

ar  adsynt2  kamp, kcps, iwfn, ifreqfn, iampfn, icnt [, iphs]

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

hsboscil :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig Source

An oscillator which takes tonality and brightness as arguments.

An oscillator which takes tonality and brightness as arguments, relative to a base frequency.

ares  hsboscil  kamp, ktone, kbrite, ibasfreq, iwfn, ioctfn \
                   [, ioctcnt] [, iphs]

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

Basic Oscillators.

lfo :: Sig -> Sig -> Sig Source

A low frequency oscillator of various shapes.

kres  lfo  kamp, kcps [, itype]
ares  lfo  kamp, kcps [, itype]

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

oscbnk :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Sig Source

Mixes the output of any number of oscillators.

This unit generator mixes the output of any number of oscillators. The frequency, phase, and amplitude of each oscillator can be modulated by two LFOs (all oscillators have a separate set of LFOs, with different phase and frequency); additionally, the output of each oscillator can be filtered through an optional parametric equalizer (also controlled by the LFOs). This opcode is most useful for rendering ensemble (strings, choir, etc.) instruments.

ares  oscbnk   kcps, kamd, kfmd, kpmd, iovrlap, iseed, kl1minf, kl1maxf, \
          kl2minf, kl2maxf, ilfomode, keqminf, keqmaxf, keqminl, keqmaxl, \
          keqminq, keqmaxq, ieqmode, kfn [, il1fn] [, il2fn] [, ieqffn]   \
          [, ieqlfn] [, ieqqfn] [, itabl] [, ioutfn]

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

oscil :: Sig -> Sig -> Tab -> Sig Source

A simple oscillator.

oscil reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp.

ares  oscil  xamp, xcps [, ifn, iphs]
kres  oscil  kamp, kcps [, ifn, iphs]

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

oscil3 :: Sig -> Sig -> Tab -> Sig Source

A simple oscillator with cubic interpolation.

oscil3 reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp. Cubic interpolation is applied for table look up from internal phase values.

ares  oscil3  xamp, xcps [, ifn, iphs]
kres  oscil3  kamp, kcps [, ifn, iphs]

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

oscili :: Sig -> Sig -> Tab -> Sig Source

A simple oscillator with linear interpolation.

oscili reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp. Linear interpolation is applied for table look up from internal phase values.

ares  oscili  xamp, xcps, ifn [, iphs]
kres  oscili  kamp, kcps, ifn [, iphs]

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

oscilikt :: Sig -> Sig -> Tab -> Sig Source

A linearly interpolated oscillator that allows changing the table number at k-rate.

oscilikt is very similar to oscili, but allows changing the table number at k-rate. It is slightly slower than oscili (especially with high control rate), although also more accurate as it uses a 31-bit phase accumulator, as opposed to the 24-bit one used by oscili.

ares  oscilikt  xamp, xcps, kfn [, iphs] [, istor]
kres  oscilikt  kamp, kcps, kfn [, iphs] [, istor]

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

osciliktp :: Sig -> Tab -> Sig -> Sig Source

A linearly interpolated oscillator that allows allows phase modulation.

osciliktp allows phase modulation (which is actually implemented as k-rate frequency modulation, by differentiating phase input). The disadvantage is that there is no amplitude control, and frequency can be varied only at the control-rate. This opcode can be faster or slower than oscilikt, depending on the control-rate.

ares  osciliktp  kcps, kfn, kphs [, istor]

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

oscilikts :: Sig -> Sig -> Tab -> Sig -> Sig -> Sig Source

A linearly interpolated oscillator with sync status that allows changing the table number at k-rate.

oscilikts is the same as oscilikt. Except it has a sync input that can be used to re-initialize the oscillator to a k-rate phase value. It is slower than oscilikt and osciliktp.

ares  oscilikts  xamp, xcps, kfn, async, kphs [, istor]

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

osciln :: Sig -> D -> Tab -> D -> Sig Source

Accesses table values at a user-defined frequency.

Accesses table values at a user-defined frequency. This opcode can also be written as oscilx.

ares  osciln  kamp, ifrq, ifn, itimes

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

oscils :: D -> D -> D -> Sig Source

A simple, fast sine oscillator

Simple, fast sine oscillator, that uses only one multiply, and two add operations to generate one sample of output, and does not require a function table.

ares  oscils  iamp, icps, iphs [, iflg]

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

poscil :: Sig -> Sig -> Tab -> Sig Source

High precision oscillator.

ares  poscil  aamp, acps [, ifn, iphs]
ares  poscil  aamp, kcps [, ifn, iphs]
ares  poscil  kamp, acps [, ifn, iphs]
ares  poscil  kamp, kcps [, ifn, iphs]
ires  poscil  kamp, kcps [, ifn, iphs]
kres  poscil  kamp, kcps [, ifn, iphs]

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

poscil3 :: Sig -> Sig -> Tab -> Sig Source

High precision oscillator with cubic interpolation.

ares  poscil3  aamp, acps [, ifn, iphs]
ares  poscil3  aamp, kcps [, ifn, iphs]
ares  poscil3  kamp, acps [, ifn, iphs]
ares  poscil3  kamp, kcps [, ifn, iphs]
ires  poscil3  kamp, kcps [, ifn, iphs]
kres  poscil3  kamp, kcps [, ifn, iphs]

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

vibr :: Sig -> Sig -> Tab -> Sig Source

Easier-to-use user-controllable vibrato.

kout  vibr  kAverageAmp, kAverageFreq, ifn

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

vibrato :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Generates a natural-sounding user-controllable vibrato.

kout  vibrato  kAverageAmp, kAverageFreq, kRandAmountAmp, kRandAmountFreq, kAmpMinRate, kAmpMaxRate, kcpsMinRate, kcpsMaxRate, ifn [, iphs

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

Dynamic Spectrum Oscillators.

buzz :: Sig -> Sig -> Sig -> Tab -> Sig Source

Output is a set of harmonically related sine partials.

ares  buzz  xamp, xcps, knh, ifn [, iphs]

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

gbuzz :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Output is a set of harmonically related cosine partials.

ares  gbuzz  xamp, xcps, knh, klh, kmul, ifn [, iphs]

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

mpulse :: Sig -> Sig -> Sig Source

Generates a set of impulses.

Generates a set of impulses of amplitude kamp separated by kintvl seconds (or samples if kintvl is negative). The first impulse is generated after a delay of ioffset seconds.

ares  mpulse  kamp, kintvl [, ioffset]

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

vco :: Sig -> Sig -> D -> Sig -> Sig Source

Implementation of a band limited, analog modeled oscillator.

Implementation of a band limited, analog modeled oscillator, based on integration of band limited impulses. vco can be used to simulate a variety of analog wave forms.

ares  vco  xamp, xcps, iwave, kpw [, ifn] [, imaxd] [, ileak] [, inyx] \
          [, iphs] [, iskip]

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

vco2 :: Sig -> Sig -> Sig Source

Implementation of a band-limited oscillator using pre-calculated tables.

vco2 is similar to vco. But the implementation uses pre-calculated tables of band-limited waveforms (see also GEN30) rather than integrating impulses. This opcode can be faster than vco (especially if a low control-rate is used) and also allows better sound quality. Additionally, there are more waveforms and oscillator phase can be modulated at k-rate. The disadvantage is increased memory usage. For more details about vco2 tables, see also vco2init and vco2ft.

ares  vco2  kamp, kcps [, imode] [, kpw] [, kphs] [, inyx]

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

vco2ft :: Sig -> D -> Tab Source

Returns a table number at k-time for a given oscillator frequency and wavform.

vco2ft returns the function table number to be used for generating the specified waveform at a given frequency. This function table number can be used by any Csound opcode that generates a signal by reading function tables (like oscilikt). The tables must be calculated by vco2init before vco2ft is called and shared as Csound ftables (ibasfn).

kfn  vco2ft  kcps, iwave [, inyx]

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

vco2ift :: D -> D -> Tab Source

Returns a table number at i-time for a given oscillator frequency and wavform.

vco2ift is the same as vco2ft, but works at i-time. It is suitable for use with opcodes that expect an i-rate table number (for example, oscili).

ifn  vco2ift  icps, iwave [, inyx]

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

vco2init :: D -> SE Tab Source

Calculates tables for use by vco2 opcode.

vco2init calculates tables for use by vco2 opcode. Optionally, it is also possible to access these tables as standard Csound function tables. In this case, vco2ft can be used to find the correct table number for a given oscillator frequency.

ifn  vco2init  iwave [, ibasfn] [, ipmul] [, iminsiz] [, imaxsiz] [, isrcft]

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

FM Synthesis.

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crossfm  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crossfmi  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crosspm  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crosspmi  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crossfmpm  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

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

Two mutually frequency and/or phase modulated oscillators.

Two oscillators, mutually frequency and/or phase modulated by each other.

a1, a2  crossfmpmi  xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]

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

fmb3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Uses FM synthesis to create a Hammond B3 organ sound.

Uses FM synthesis to create a Hammond B3 organ sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmb3  kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, ifn3, \
          ifn4, ivfn]

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

fmbell :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Uses FM synthesis to create a tublar bell sound.

Uses FM synthesis to create a tublar bell sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmbell  kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, ifn3, \
          ifn4, ivfn, isus]

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

fmmetal :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig Source

Uses FM synthesis to create a “Heavy Metal” sound.

Uses FM synthesis to create a “Heavy Metal” sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmmetal  kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, ifn3, \
          ifn4, ivfn

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

fmpercfl :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Uses FM synthesis to create a percussive flute sound.

Uses FM synthesis to create a percussive flute sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmpercfl  kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, \
          ifn3, ifn4, ivfn]

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

fmrhode :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig Source

Uses FM synthesis to create a Fender Rhodes electric piano sound.

Uses FM synthesis to create a Fender Rhodes electric piano sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmrhode  kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, \
          ifn3, ifn4, ivfn

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

fmvoice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

FM Singing Voice Synthesis

ares  fmvoice  kamp, kfreq, kvowel, ktilt, kvibamt, kvibrate[, ifn1, \
          ifn2, ifn3, ifn4, ivibfn]

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

fmwurlie :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig Source

Uses FM synthesis to create a Wurlitzer electric piano sound.

Uses FM synthesis to create a Wurlitzer electric piano sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.

ares  fmwurlie  kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, ifn3, \
          ifn4, ivfn

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

foscil :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

A basic frequency modulated oscillator.

ares  foscil  xamp, kcps, xcar, xmod, kndx, ifn [, iphs]

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

foscili :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Basic frequency modulated oscillator with linear interpolation.

ares  foscili  xamp, kcps, xcar, xmod, kndx, ifn [, iphs]

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

Granular Synthesis.

diskgrain :: Str -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig Source

Synchronous granular synthesis, using a soundfile as source.

diskgrain implements synchronous granular synthesis. The source sound for the grains is obtained by reading a soundfile containing the samples of the source waveform.

asig  diskgrain  Sfname, kamp, kfreq, kpitch, kgrsize, kprate, \
          ifun, iolaps [,imaxgrsize , ioffset]

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

fof :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig Source

Produces sinusoid bursts useful for formant and granular synthesis.

Audio output is a succession of sinusoid bursts initiated at frequency xfund with a spectral peak at xform. For xfund above 25 Hz these bursts produce a speech-like formant with spectral characteristics determined by the k-input parameters. For lower fundamentals this generator provides a special form of granular synthesis.

ares  fof  xamp, xfund, xform, koct, kband, kris, kdur, kdec, iolaps, \
          ifna, ifnb, itotdur [, iphs] [, ifmode] [, iskip]

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

fof2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig -> Sig -> Sig Source

Produces sinusoid bursts including k-rate incremental indexing with each successive burst.

Audio output is a succession of sinusoid bursts initiated at frequency xfund with a spectral peak at xform. For xfund above 25 Hz these bursts produce a speech-like formant with spectral characteristics determined by the k-input parameters. For lower fundamentals this generator provides a special form of granular synthesis.

ares  fof2  xamp, xfund, xform, koct, kband, kris, kdur, kdec, iolaps, \
          ifna, ifnb, itotdur, kphs, kgliss [, iskip]

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

fog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig Source

Audio output is a succession of grains derived from data in a stored function table

Audio output is a succession of grains derived from data in a stored function table ifna. The local envelope of these grains and their timing is based on the model of fof synthesis and permits detailed control of the granular synthesis.

ares  fog  xamp, xdens, xtrans, aspd, koct, kband, kris, kdur, kdec, \
          iolaps, ifna, ifnb, itotdur [, iphs] [, itmode] [, iskip]

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

grain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> D -> Sig Source

Generates granular synthesis textures.

ares  grain  xamp, xpitch, xdens, kampoff, kpitchoff, kgdur, igfn, \
          iwfn, imgdur [, igrnd]

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

grain2 :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig Source

Easy-to-use granular synthesis texture generator.

Generate granular synthesis textures. grain2 is simpler to use, but grain3 offers more control.

ares  grain2  kcps, kfmd, kgdur, iovrlp, kfn, iwfn [, irpow] \
          [, iseed] [, imode]

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

grain3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig -> Sig -> Sig Source

Generate granular synthesis textures with more user control.

Generate granular synthesis textures. grain2 is simpler to use but grain3 offers more control.

ares  grain3  kcps, kphs, kfmd, kpmd, kgdur, kdens, imaxovr, kfn, iwfn, \
          kfrpow, kprpow [, iseed] [, imode]

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

granule :: Sig -> D -> D -> D -> D -> Tab -> D -> D -> D -> D -> Sig -> D -> Sig -> D -> D -> D -> Sig Source

A more complex granular synthesis texture generator.

The granule unit generator is more complex than grain, but does add new possibilities.

ares  granule  xamp, ivoice, iratio, imode, ithd, ifn, ipshift, igskip, \
          igskip_os, ilength, kgap, igap_os, kgsize, igsize_os, iatt, idec \
          [, iseed] [, ipitch1] [, ipitch2] [, ipitch3] [, ipitch4] [, ifnenv]

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

partikkel :: Tuple a => Sig -> Sig -> D -> Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> D -> D -> Sig -> D -> Sig -> D -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> a Source

Granular synthesizer with "per grain" control over many of its parameters. Has a sync input to sychronize its internal grain scheduler clock to an external clock source.

partikkel was conceived after reading Curtis Roads' book Microsound, and the goal was to create an opcode that was capable of all time-domain varieties of granular synthesis described in this book. The idea being that most of the techniques only differ in parameter values, and by having a single opcode that can do all varieties of granular synthesis makes it possible to interpolate between techniques. Granular synthesis is sometimes dubbed particle synthesis, and it was thought apt to name the opcode partikkel to distinguish it from other granular opcodes.

a1 [, a2, a3, a4, a5, a6, a7, a8]  partikkel  agrainfreq, \
                  kdistribution, idisttab, async, kenv2amt, ienv2tab, ienv_attack, \
                  ienv_decay, ksustain_amount, ka_d_ratio, kduration, kamp, igainmasks, \
                  kwavfreq, ksweepshape, iwavfreqstarttab, iwavfreqendtab, awavfm, \
                  ifmamptab, kfmenv, icosine, ktraincps, knumpartials, kchroma, \
                  ichannelmasks, krandommask, kwaveform1, kwaveform2, kwaveform3, \
                  kwaveform4, iwaveamptab, asamplepos1, asamplepos2, asamplepos3, \
                  asamplepos4, kwavekey1, kwavekey2, kwavekey3, kwavekey4, imax_grains \
                  [, iopcode_id]

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

partikkelsync :: Tuple a => D -> a Source

Outputs partikkel's grain scheduler clock pulse and phase to synchronize several instances of the partikkel opcode to the same clock source.

partikkelsync is an opcode for outputting partikkel's grain scheduler clock pulse and phase. partikkelsync's output can be used to synchronize other instances of the partikkel opcode to the same clock.

async [,aphase]  partikkelsync  iopcode_id

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

sndwarp :: Tuple a => Sig -> Sig -> Sig -> Tab -> D -> D -> D -> D -> Tab -> D -> a Source

Reads a mono sound sample from a table and applies time-stretching and/or pitch modification.

sndwarp reads sound samples from a table and applies time-stretching and/or pitch modification. Time and frequency modification are independent from one another. For example, a sound can be stretched in time while raising the pitch!

ares [, ac]  sndwarp  xamp, xtimewarp, xresample, ifn1, ibeg, iwsize, \
          irandw, ioverlap, ifn2, itimemode

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

sndwarpst :: Tuple a => Sig -> Sig -> Sig -> Tab -> D -> D -> D -> D -> Tab -> D -> a Source

Reads a stereo sound sample from a table and applies time-stretching and/or pitch modification.

sndwarpst reads stereo sound samples from a table and applies time-stretching and/or pitch modification. Time and frequency modification are independent from one another. For example, a sound can be stretched in time while raising the pitch!

ar1, ar2 [,ac1] [, ac2]  sndwarpst  xamp, xtimewarp, xresample, ifn1, \
          ibeg, iwsize, irandw, ioverlap, ifn2, itimemode

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

syncgrain :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig Source

Synchronous granular synthesis.

syncgrain implements synchronous granular synthesis. The source sound for the grains is obtained by reading a function table containing the samples of the source waveform. For sampled-sound sources, GEN01 is used. syncgrain will accept deferred allocation tables.

asig  syncgrain  kamp, kfreq, kpitch, kgrsize, kprate, ifun1, \
          ifun2, iolaps

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

syncloop :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig Source

Synchronous granular synthesis.

syncloop is a variation on syncgrain, which implements synchronous granular synthesis. syncloop adds loop start and end points and an optional start position. Loop start and end control grain start positions, so the actual grains can go beyond the loop points (if the loop points are not at the extremes of the table), enabling seamless crossfading. For more information on the granular synthesis process, check the syncgrain manual page.

asig  syncloop  kamp, kfreq, kpitch, kgrsize, kprate, klstart, \
          klend, ifun1, ifun2, iolaps[,istart, iskip]

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

vosim :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Simple vocal simulation based on glottal pulses with formant characteristics.

This opcode produces a simple vocal simulation based on glottal pulses with formant characteristics. Output is a series of sound events, where each event is composed of a burst of squared sine pulses followed by silence. The VOSIM (VOcal SIMulation) synthesis method was developed by Kaegi and Tempelaars in the 1970's.

ar  vosim  kamp, kFund, kForm, kDecay, kPulseCount, kPulseFactor, ifn [, iskip]

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

Hyper Vectorial Synthesis.

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

Allows one-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

hvs1 allows one-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

 hvs1  kx, inumParms, inumPointsX, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]

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

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

Allows two-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

hvs2 allows two-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

 hvs2  kx, ky, inumParms, inumPointsX, inumPointsY, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]

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

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

Allows three-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

hvs3 allows three-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.

 hvs3  kx, ky, kz, inumParms, inumPointsX, inumPointsY, inumPointsZ, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]

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

Linear and Exponential Generators.

cosseg :: [D] -> Sig Source

Trace a series of line segments between specified points with cosine interpolation.

ares  cosseg  ia, idur1, ib [, idur2] [, ic] [...]
kres  cosseg  ia, idur1, ib [, idur2] [, ic] [...]

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

cossegb :: [D] -> Sig Source

Trace a series of line segments between specified absolute points with cosine interpolation.

ares  cossegb  ia, itim1, ib [, itim2] [, ic] [...]
kres  cossegb  ia, itim1, ib [, itim2] [, ic] [...]

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

cossegr :: [D] -> D -> D -> Sig Source

Trace a series of line segments between specified points with cosine interpolation, including a release segment.

ares  cossegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz
kres  cossegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz

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

expcurve :: Sig -> Sig -> Sig Source

This opcode implements a formula for generating a normalised exponential curve in range 0 - 1. It is based on the Max / MSP work of Eric Singer (c) 1994.

Generates an exponential curve in range 0 to 1 of arbitrary steepness. Steepness index equal to or lower than 1.0 will result in Not-a-Number errors and cause unstable behavior.

kout  expcurve  kindex, ksteepness

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

expon :: D -> D -> D -> Sig Source

Trace an exponential curve between specified points.

ares  expon  ia, idur, ib
kres  expon  ia, idur, ib

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

expseg :: [D] -> Sig Source

Trace a series of exponential segments between specified points.

ares  expseg  ia, idur1, ib [, idur2] [, ic] [...]
kres  expseg  ia, idur1, ib [, idur2] [, ic] [...]

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

expsega :: [D] -> Sig Source

An exponential segment generator operating at a-rate.

An exponential segment generator operating at a-rate. This unit is almost identical to expseg, but more precise when defining segments with very short durations (i.e., in a percussive attack phase) at audio rate.

ares  expsega  ia, idur1, ib [, idur2] [, ic] [...]

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

expsegb :: [D] -> Sig Source

Trace a series of exponential segments between specified absolute points.

ares  expsegb  ia, itim1, ib [, itim2] [, ic] [...]
kres  expsegb  ia, itim1, ib [, itim2] [, ic] [...]

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

expsegba :: D -> D -> D -> Sig Source

An exponential segment generator operating at a-rate with absolute times.

An exponential segment generator operating at a-rate. This unit is almost identical to expsegb, but more precise when defining segments with very short durations (i.e., in a percussive attack phase) at audio rate.

ares  expsegba  ia, itim1, ib [, itim2] [, ic] [...]

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

expsegr :: [D] -> D -> D -> Sig Source

Trace a series of exponential segments between specified points including a release segment.

ares  expsegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz
kres  expsegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz

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

gainslider :: Sig -> Sig Source

An implementation of a logarithmic gain curve which is similar to the gainslider~ object from Cycling 74 Max / MSP.

This opcode is intended for use to multiply by an audio signal to give a console mixer like feel. There is no bounds in the source code so you can for example give higher than 127 values for extra amplitude but possibly clipped audio.

kout  gainslider  kindex

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

jspline :: Sig -> Sig -> Sig -> SE Sig Source

A jitter-spline generator.

ares  jspline  xamp, kcpsMin, kcpsMax
kres  jspline  kamp, kcpsMin, kcpsMax

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

line :: D -> D -> D -> Sig Source

Trace a straight line between specified points.

ares  line  ia, idur, ib
kres  line  ia, idur, ib

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

linseg :: [D] -> Sig Source

Trace a series of line segments between specified points.

ares  linseg  ia, idur1, ib [, idur2] [, ic] [...]
kres  linseg  ia, idur1, ib [, idur2] [, ic] [...]

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

linsegb :: [D] -> Sig Source

Trace a series of line segments between specified absolute points.

ares  linsegb  ia, itim1, ib [, itim2] [, ic] [...]
kres  linsegb  ia, itim1, ib [, itim2] [, ic] [...]

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

linsegr :: [D] -> D -> D -> Sig Source

Trace a series of line segments between specified points including a release segment.

ares  linsegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz
kres  linsegr  ia, idur1, ib [, idur2] [, ic] [...], irel, iz

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

logcurve :: Sig -> Sig -> Sig Source

This opcode implements a formula for generating a normalised logarithmic curve in range 0 - 1. It is based on the Max / MSP work of Eric Singer (c) 1994.

Generates a logarithmic curve in range 0 to 1 of arbitrary steepness. Steepness index equal to or lower than 1.0 will result in Not-a-Number errors and cause unstable behavior.

kout  logcurve  kindex, ksteepness

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

loopseg :: Sig -> Sig -> D -> [Sig] -> Sig Source

Generate control signal consisting of linear segments delimited by two or more specified points.

Generate control signal consisting of linear segments delimited by two or more specified points. The entire envelope is looped at kfreq rate. Each parameter can be varied at k-rate.

ksig  loopseg  kfreq, ktrig, iphase, ktime0, kvalue0 [, ktime1] [, kvalue1] \
          [, ktime2] [, kvalue2] [...]

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

loopsegp :: Sig -> [Sig] -> Sig Source

Control signals based on linear segments.

Generate control signal consisiting of linear segments delimited by two or more specified points. The entire envelope can be looped at time-variant rate. Each segment coordinate can also be varied at k-rate.

ksig  loopsegp   kphase, kvalue0, kdur0, kvalue1 \
          [, kdur1, ... , kdurN-1, kvalueN]

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

looptseg :: Sig -> Sig -> [Sig] -> Sig Source

Generate control signal consisting of exponential or linear segments delimited by two or more specified points.

Generate control signal consisting of controllable exponential segments or linear segments delimited by two or more specified points. The entire envelope is looped at kfreq rate. Each parameter can be varied at k-rate.

ksig  looptseg  kfreq, ktrig, ktime0, kvalue0, ktype0, [, ktime1] [, kvalue1] [,ktype1] \
          [, ktime2] [, kvalue2] [,ktype2] [...][, ktimeN] [, kvalueN]

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

loopxseg :: Sig -> Sig -> D -> [Sig] -> Sig Source

Generate control signal consisting of exponential segments delimited by two or more specified points.

Generate control signal consisting of exponential segments delimited by two or more specified points. The entire envelope is looped at kfreq rate. Each parameter can be varied at k-rate.

ksig  loopxseg  kfreq, ktrig, iphase, ktime0, kvalue0 [, ktime1] [, kvalue1] \
          [, ktime2] [, kvalue2] [...]

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

lpshold :: Sig -> Sig -> D -> [Sig] -> Sig Source

Generate control signal consisting of held segments.

Generate control signal consisting of held segments delimited by two or more specified points. The entire envelope is looped at kfreq rate. Each parameter can be varied at k-rate.

ksig  lpshold  kfreq, ktrig, iphase, ktime0, kvalue0  [, ktime1] [, kvalue1] [, ktime2] [, kvalue2] [...]

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

lpsholdp :: Sig -> Sig -> [Sig] -> Sig Source

Control signals based on held segments.

Generate control signal consisiting of held segments delimited by two or more specified points. The entire envelope can be looped at time-variant rate. Each segment coordinate can also be varied at k-rate.

ksig  lpsholdp   kphase, ktrig, ktime0, kvalue0  [, ktime1] [, kvalue1] \
          [, ktime2] [, kvalue2] [...]

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

rspline :: Sig -> Sig -> Sig -> Sig -> SE Sig Source

Generate random spline curves.

ares  rspline  xrangeMin, xrangeMax, kcpsMin, kcpsMax
kres  rspline  krangeMin, krangeMax, kcpsMin, kcpsMax

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

scale :: Sig -> Sig -> Sig -> Sig Source

Arbitrary signal scaling.

Scales incoming value to user-definable range. Similar to scale object found in popular dataflow languages.

kscl  scale  kinput, kmax, kmin

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

transeg :: [D] -> Sig Source

Constructs a user-definable envelope.

ares  transeg  ia, idur, itype, ib [, idur2] [, itype] [, ic] ...
kres  transeg  ia, idur, itype, ib [, idur2] [, itype] [, ic] ...

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

transegb :: [D] -> Sig Source

Constructs a user-definable envelope in absolute time.

ares  transegb  ia, itim, itype, ib [, itim2] [, itype] [, ic] ...
kres  transegb  ia, itim, itype, ib [, itim2] [, itype] [, ic] ...

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

transegr :: [D] -> D -> D -> D -> Sig Source

Constructs a user-definable envelope with extended release segment.

Constructs a user-definable envelope. It is the same as transeg, with an extended release segment.

ares  transegr  ia, idur, itype, ib [, idur2] [, itype] [, ic] ...
kres  transegr  ia, idur, itype, ib [, idur2] [, itype] [, ic] ...

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

Envelope Generators.

adsr :: D -> D -> D -> D -> Sig Source

Calculates the classical ADSR envelope using linear segments.

ares  adsr  iatt, idec, islev, irel [, idel]
kres  adsr  iatt, idec, islev, irel [, idel]

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

envlpx :: Sig -> D -> D -> D -> Tab -> D -> D -> Sig Source

Applies an envelope consisting of 3 segments.

envlpx -- apply an envelope consisting of 3 segments:

ares  envlpx  xamp, irise, idur, idec, ifn, iatss, iatdec [, ixmod]
kres  envlpx  kamp, irise, idur, idec, ifn, iatss, iatdec [, ixmod]

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

envlpxr :: Sig -> D -> D -> Tab -> D -> D -> Sig Source

The envlpx opcode with a final release segment.

envlpxr is the same as envlpx except that the final segment is entered only on sensing a MIDI note release. The note is then extended by the decay time.

ares  envlpxr  xamp, irise, idec, ifn, iatss, iatdec [, ixmod] [,irind]
kres  envlpxr  kamp, irise, idec, ifn, iatss, iatdec [, ixmod] [,irind]

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

linen :: Sig -> D -> D -> D -> Sig Source

Applies a straight line rise and decay pattern to an input amp signal.

linen -- apply a straight line rise and decay pattern to an input amp signal.

ares  linen  xamp, irise, idur, idec
kres  linen  kamp, irise, idur, idec

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

linenr :: Sig -> D -> D -> D -> Sig Source

The linen opcode extended with a final release segment.

linenr -- same as linen except that the final segment is entered only on sensing a MIDI note release. The note is then extended by the decay time.

ares  linenr  xamp, irise, idec, iatdec
kres  linenr  kamp, irise, idec, iatdec

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

madsr :: D -> D -> D -> D -> Sig Source

Calculates the classical ADSR envelope using the linsegr mechanism.

ares  madsr  iatt, idec, islev, irel [, idel] [, ireltim]
kres  madsr  iatt, idec, islev, irel [, idel] [, ireltim]

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

mxadsr :: D -> D -> D -> D -> Sig Source

Calculates the classical ADSR envelope using the expsegr mechanism.

ares  mxadsr  iatt, idec, islev, irel [, idel] [, ireltim]
kres  mxadsr  iatt, idec, islev, irel [, idel] [, ireltim]

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

xadsr :: D -> D -> D -> D -> Sig Source

Calculates the classical ADSR envelope.

Calculates the classical ADSR envelope

ares  xadsr  iatt, idec, islev, irel [, idel]
kres  xadsr  iatt, idec, islev, irel [, idel]

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

Models and Emulations.

bamboo :: Sig -> D -> Sig Source

Semi-physical model of a bamboo sound.

bamboo is a semi-physical model of a bamboo sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  bamboo  kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \
          [, ifreq1] [, ifreq2]

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

barmodel :: Sig -> Sig -> D -> D -> Sig -> D -> D -> D -> D -> Sig Source

Creates a tone similar to a struck metal bar.

Audio output is a tone similar to a struck metal bar, using a physical model developed from solving the partial differential equation. There are controls over the boundary conditions as well as the bar characteristics.

ares  barmodel  kbcL, kbcR, iK, ib, kscan, iT30, ipos, ivel, iwid

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

cabasa :: D -> D -> Sig Source

Semi-physical model of a cabasa sound.

cabasa is a semi-physical model of a cabasa sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  cabasa  iamp, idettack [, inum] [, idamp] [, imaxshake]

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

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

Simulates Chua's oscillator, an LRC oscillator with an active resistor, proved capable of bifurcation and chaotic attractors, with k-rate control of circuit elements.

aI3, aV2, aV1  chuap  kL, kR0, kC1, kG, kGa, kGb, kE, kC2, iI3, iV2, iV1, ktime_step

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

crunch :: D -> D -> Sig Source

Semi-physical model of a crunch sound.

crunch is a semi-physical model of a crunch sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  crunch  iamp, idettack [, inum] [, idamp] [, imaxshake]

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

dripwater :: Sig -> D -> Sig Source

Semi-physical model of a water drop.

dripwater is a semi-physical model of a water drop. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  dripwater  kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \
          [, ifreq1] [, ifreq2]

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

gendy :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.

Implementation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.

ares  gendy  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
               kampscl, kdurscl [, initcps] [, knum]
kres  gendy  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
               kampscl, kdurscl [, initcps] [, knum]

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

gendyc :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Dynamic stochastic approach to waveform synthesis using cubic interpolation.

Implementation with cubic interpolation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.

ares  gendyc  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
                kampscl, kdurscl [, initcps] [, knum]
kres  gendyc  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
                kampscl, kdurscl [, initcps] [, knum]

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

gendyx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Variation of the dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.

gendyx (gendy eXtended) is an implementation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis, using curves instead of segments.

ares  gendyx  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
                kampscl, kdurscl, kcurveup, kcurvedown [, initcps] [, knum]
kres  gendyx  kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \
                kampscl, kdurscl, kcurveup, kcurvedown [, initcps] [, knum]

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

gogobel :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> Sig Source

Audio output is a tone related to the striking of a cow bell or similar.

Audio output is a tone related to the striking of a cow bell or similar. The method is a physical model developed from Perry Cook, but re-coded for Csound.

ares  gogobel  kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivfn

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

guiro :: Sig -> D -> Sig Source

Semi-physical model of a guiro sound.

guiro is a semi-physical model of a guiro sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  guiro  kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] [, ifreq1]

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

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

Implements the Lorenz system of equations.

Implements the Lorenz system of equations. The Lorenz system is a chaotic-dynamic system which was originally used to simulate the motion of a particle in convection currents and simplified weather systems. Small differences in initial conditions rapidly lead to diverging values. This is sometimes expressed as the butterfly effect. If a butterfly flaps its wings in Australia, it will have an effect on the weather in Alaska. This system is one of the milestones in the development of chaos theory. It is useful as a chaotic audio source or as a low frequency modulation source.

ax, ay, az  lorenz  ksv, krv, kbv, kh, ix, iy, iz, iskip [, iskipinit]

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

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

Mandelbrot set

Returns the number of iterations corresponding to a given point of complex plane by applying the Mandelbrot set formula.

kiter, koutrig  mandel   ktrig, kx, ky, kmaxIter

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

mandol :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

An emulation of a mandolin.

ares  mandol  kamp, kfreq, kpluck, kdetune, kgain, ksize, ifn [, iminfreq]

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

marimba :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig Source

Physical model related to the striking of a wooden block.

Audio output is a tone related to the striking of a wooden block as found in a marimba. The method is a physical model developed from Perry Cook but re-coded for Csound.

ares  marimba  kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec \
          [, idoubles] [, itriples]

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

moog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Sig Source

An emulation of a mini-Moog synthesizer.

ares  moog  kamp, kfreq, kfiltq, kfiltrate, kvibf, kvamp, iafn, iwfn, ivfn

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

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

Simulates a planet orbiting in a binary star system.

planet simulates a planet orbiting in a binary star system. The outputs are the x, y and z coordinates of the orbiting planet. It is possible for the planet to achieve escape velocity by a close encounter with a star. This makes this system somewhat unstable.

ax, ay, az  planet  kmass1, kmass2, ksep, ix, iy, iz, ivx, ivy, ivz, idelta \
          [, ifriction] [, iskip]

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

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

Creates a tone similar to a piano string prepared in a Cageian fashion.

Audio output is a tone similar to a piano string, prepared with a number of rubbers and rattles. The method uses a physical model developed from solving the partial differential equation.

ares  prepiano  ifreq, iNS, iD, iK, \
        iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, \
        isspread[, irattles, irubbers]
al,ar  prepiano  ifreq, iNS, iD, iK, \
        iT30,iB, kbcl, kbcr, imass, ifreq, iinit, ipos, ivel, isfreq, \
        isspread[, irattles, irubbers]

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

sandpaper :: D -> D -> Sig Source

Semi-physical model of a sandpaper sound.

sandpaper is a semi-physical model of a sandpaper sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  sandpaper  iamp, idettack [, inum] [, idamp] [, imaxshake]

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

sekere :: D -> D -> Sig Source

Semi-physical model of a sekere sound.

sekere is a semi-physical model of a sekere sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  sekere  iamp, idettack [, inum] [, idamp] [, imaxshake]

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

shaker :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Sounds like the shaking of a maraca or similar gourd instrument.

Audio output is a tone related to the shaking of a maraca or similar gourd instrument. The method is a physically inspired model developed from Perry Cook, but re-coded for Csound.

ares  shaker  kamp, kfreq, kbeans, kdamp, ktimes [, idecay]

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

sleighbells :: Sig -> D -> Sig Source

Semi-physical model of a sleighbell sound.

sleighbells is a semi-physical model of a sleighbell sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  sleighbells  kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \
          [, ifreq1] [, ifreq2]

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

stix :: D -> D -> Sig Source

Semi-physical model of a stick sound.

stix is a semi-physical model of a stick sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  stix  iamp, idettack [, inum] [, idamp] [, imaxshake]

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

tambourine :: Sig -> D -> Sig Source

Semi-physical model of a tambourine sound.

tambourine is a semi-physical model of a tambourine sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

ares  tambourine  kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \
          [, ifreq1] [, ifreq2]

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

vibes :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig Source

Physical model related to the striking of a metal block.

Audio output is a tone related to the striking of a metal block as found in a vibraphone. The method is a physical model developed from Perry Cook, but re-coded for Csound.

ares  vibes  kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec

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

voice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Sig Source

An emulation of a human voice.

ares  voice  kamp, kfreq, kphoneme, kform, kvibf, kvamp, ifn, ivfn

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

Phasors.

phasor :: Sig -> Sig Source

Produce a normalized moving phase value.

ares  phasor  xcps [, iphs]
kres  phasor  kcps [, iphs]

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

phasorbnk :: Sig -> Sig -> D -> Sig Source

Produce an arbitrary number of normalized moving phase values.

Produce an arbitrary number of normalized moving phase values, accessable by an index.

ares  phasorbnk  xcps, kndx, icnt [, iphs]
kres  phasorbnk  kcps, kndx, icnt [, iphs]

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

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

Produces a normalized moving phase value with sync input and output.

Produces a moving phase value between zero and one and an extra impulse output ("sync out") whenever its phase value crosses or is reset to zero. The phase can be reset at any time by an impulse on the "sync in" parameter.

aphase, asyncout  syncphasor  xcps, asyncin, [, iphs]

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

Random (Noise) Generators.

betarand :: SigOrD a => a -> a -> a -> SE a Source

Beta distribution random number generator (positive values only).

Beta distribution random number generator (positive values only). This is an x-class noise generator.

ares  betarand  krange, kalpha, kbeta
ires  betarand  krange, kalpha, kbeta
kres  betarand  krange, kalpha, kbeta

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

bexprnd :: SigOrD a => a -> SE a Source

Exponential distribution random number generator.

Exponential distribution random number generator. This is an x-class noise generator.

ares  bexprnd  krange
ires  bexprnd  krange
kres  bexprnd  krange

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

cauchy :: SigOrD a => a -> SE a Source

Cauchy distribution random number generator.

Cauchy distribution random number generator. This is an x-class noise generator.

ares  cauchy  kalpha
ires  cauchy  kalpha
kres  cauchy  kalpha

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

cauchyi :: SigOrD a => a -> a -> a -> SE a Source

Cauchy distribution random number generator with interpolation.

Cauchy distribution random number generator with controlled interpolation between values. This is an x-class noise generator.

ares  cauchyi  klambda, xamp, xcps
ires  cauchyi  klambda, xamp, xcps
kres  cauchyi  klambda, xamp, xcps

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

cuserrnd :: SigOrD a => a -> a -> a -> SE a Source

Continuous USER-defined-distribution RaNDom generator.

aout  cuserrnd  kmin, kmax, ktableNum
iout  cuserrnd  imin, imax, itableNum
kout  cuserrnd  kmin, kmax, ktableNum

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

duserrnd :: SigOrD a => a -> SE a Source

Discrete USER-defined-distribution RaNDom generator.

aout  duserrnd  ktableNum
iout  duserrnd  itableNum
kout  duserrnd  ktableNum

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

dust :: Sig -> Sig -> SE Sig Source

Random impulses.

Generates random impulses from 0 to 1.

ares  dust  kamp, kdensity
kres  dust  kamp, kdensity

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

dust2 :: Sig -> Sig -> SE Sig Source

Random impulses.

Generates random impulses from -1 to 1.

ares  dust2  kamp, kdensity
kres  dust2  kamp, kdensity

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

exprand :: SigOrD a => a -> SE a Source

Exponential distribution random number generator (positive values only).

Exponential distribution random number generator (positive values only). This is an x-class noise generator.

ares  exprand  klambda
ires  exprand  klambda
kres  exprand  klambda

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

exprandi :: SigOrD a => a -> a -> a -> SE a Source

Exponential distribution random number generator with interpolation (positive values only).

Exponential distribution random number generator with controlled interpolation between values (positive values only). This is an x-class noise generator.

ares  exprandi  klambda, xamp, xcps
ires  exprandi  klambda, xamp, xcps
kres  exprandi  klambda, xamp, xcps

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

fractalnoise :: Sig -> Sig -> SE Sig Source

A fractal noise generator.

A fractal noise generator implemented as a white noise filtered by a cascade of 15 first-order filters.

ares  fractalnoise  kamp, kbeta

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

gauss :: Sig -> SE Sig Source

Gaussian distribution random number generator.

Gaussian distribution random number generator. This is an x-class noise generator.

ares  gauss  krange
ires  gauss  krange
kres  gauss  krange

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

gaussi :: SigOrD a => a -> a -> a -> SE a Source

Gaussian distribution random number generator with interpolation.

Gaussian distribution random number generator with controlled interpolation between values. This is an x-class noise generator.

ares  gaussi  krange, xamp, xcps
ires  gaussi  krange, xamp, xcps
kres  gaussi  krange, xamp, xcps

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

gausstrig :: Sig -> Sig -> Sig -> SE Sig Source

Random impulses around a certain frequency.

Generates random impulses around a certain frequency.

ares  gausstrig  kamp, kcps, kdev [, imode]
kres  gausstrig  kamp, kcps, kdev [, imode]

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

jitter :: Sig -> Sig -> Sig -> SE Sig Source

Generates a segmented line whose segments are randomly generated.

kout  jitter  kamp, kcpsMin, kcpsMax

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

jitter2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE Sig Source

Generates a segmented line with user-controllable random segments.

kout  jitter2  ktotamp, kamp1, kcps1, kamp2, kcps2, kamp3, kcps3

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

linrand :: SigOrD a => a -> SE a Source

Linear distribution random number generator (positive values only).

Linear distribution random number generator (positive values only). This is an x-class noise generator.

ares  linrand  krange
ires  linrand  krange
kres  linrand  krange

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

noise :: Sig -> Sig -> SE Sig Source

A white noise generator with an IIR lowpass filter.

ares  noise  xamp, kbeta

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

pcauchy :: SigOrD a => a -> SE a Source

Cauchy distribution random number generator (positive values only).

Cauchy distribution random number generator (positive values only). This is an x-class noise generator.

ares  pcauchy  kalpha
ires  pcauchy  kalpha
kres  pcauchy  kalpha

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

pinkish :: Sig -> SE Sig Source

Generates approximate pink noise.

Generates approximate pink noise (-3dB/oct response) by one of two different methods:

ares  pinkish  xin [, imethod] [, inumbands] [, iseed] [, iskip]

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

poisson :: SigOrD a => a -> SE a Source

Poisson distribution random number generator (positive values only).

Poisson distribution random number generator (positive values only). This is an x-class noise generator.

ares  poisson  klambda
ires  poisson  klambda
kres  poisson  klambda

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

rand :: Sig -> SE Sig Source

Generates a controlled random number series.

Output is a controlled random number series between -amp and +amp

ares  rand  xamp [, iseed] [, isel] [, ioffset]
kres  rand  xamp [, iseed] [, isel] [, ioffset]

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

randh :: Sig -> Sig -> SE Sig Source

Generates random numbers and holds them for a period of time.

ares  randh  xamp, xcps [, iseed] [, isize] [, ioffset]
kres  randh  kamp, kcps [, iseed] [, isize] [, ioffset]

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

randi :: Sig -> Sig -> SE Sig Source

Generates a controlled random number series with interpolation between each new number.

ares  randi  xamp, xcps [, iseed] [, isize] [, ioffset]
kres  randi  kamp, kcps [, iseed] [, isize] [, ioffset]

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

random :: SigOrD a => a -> a -> SE a Source

Generates a controlled pseudo-random number series between min and max values.

Generates is a controlled pseudo-random number series between min and max values.

ares  random  kmin, kmax
ires  random  imin, imax
kres  random  kmin, kmax

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

randomh :: Sig -> Sig -> Sig -> SE Sig Source

Generates random numbers with a user-defined limit and holds them for a period of time.

ares  randomh  kmin, kmax, xcps [,imode] [,ifirstval]
kres  randomh  kmin, kmax, kcps [,imode] [,ifirstval]

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

randomi :: Sig -> Sig -> Sig -> SE Sig Source

Generates a user-controlled random number series with interpolation between each new number.

ares  randomi  kmin, kmax, xcps [,imode] [,ifirstval]
kres  randomi  kmin, kmax, kcps [,imode] [,ifirstval]

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

rnd31 :: SigOrD a => a -> a -> SE a Source

31-bit bipolar random opcodes with controllable distribution.

31-bit bipolar random opcodes with controllable distribution. These units are portable, i.e. using the same seed value will generate the same random sequence on all systems. The distribution of generated random numbers can be varied at k-rate.

ax  rnd31  kscl, krpow [, iseed]
ix  rnd31  iscl, irpow [, iseed]
kx  rnd31  kscl, krpow [, iseed]

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

seed :: D -> SE () Source

Sets the global seed value.

Sets the global seed value for all x-class noise generators, as well as other opcodes that use a random call, such as grain.

 seed  ival

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

trandom :: Sig -> Sig -> Sig -> SE Sig Source

Generates a controlled pseudo-random number series between min and max values according to a trigger.

Generates a controlled pseudo-random number series between min and max values at k-rate whenever the trigger parameter is different to 0.

kout  trandom  ktrig, kmin, kmax

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

trirand :: SigOrD a => a -> SE a Source

Triangular distribution random number generator

Triangular distribution random number generator. This is an x-class noise generator.

ares  trirand  krange
ires  trirand  krange
kres  trirand  krange

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

unirand :: SigOrD a => a -> SE a Source

Uniform distribution random number generator (positive values only).

Uniform distribution random number generator (positive values only). This is an x-class noise generator.

ares  unirand  krange
ires  unirand  krange
kres  unirand  krange

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

urandom :: SigOrD a => SE a Source

truly random opcodes with controllable range.

truly random opcodes with controllable range. These units are for Linux only and use devurandom to construct Csound random values

ax  urandom  [imin, imax]
ix  urandom  [imin, imax]
kx  urandom  [imin, imax]

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

urd :: SigOrD a => a -> SE a Source

A discrete user-defined-distribution random generator that can be used as a function.

aout =  urd (ktableNum)
iout =  urd (itableNum)
kout =  urd (ktableNum)

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

weibull :: SigOrD a => a -> a -> SE a Source

Weibull distribution random number generator (positive values only).

Weibull distribution random number generator (positive values only). This is an x-class noise generator

ares  weibull  ksigma, ktau
ires  weibull  ksigma, ktau
kres  weibull  ksigma, ktau

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

Sample Playback.

bbcutm :: Sig -> D -> D -> D -> D -> D -> Sig Source

Generates breakbeat-style cut-ups of a mono audio stream.

The BreakBeat Cutter automatically generates cut-ups of a source audio stream in the style of drum and bass/jungle breakbeat manipulations. There are two versions, for mono (bbcutm) or stereo (bbcuts) sources. Whilst originally based on breakbeat cutting, the opcode can be applied to any type of source audio.

a1  bbcutm  asource, ibps, isubdiv, ibarlength, iphrasebars, inumrepeats \
          [, istutterspeed] [, istutterchance] [, ienvchoice ]

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

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

Generates breakbeat-style cut-ups of a stereo audio stream.

The BreakBeat Cutter automatically generates cut-ups of a source audio stream in the style of drum and bass/jungle breakbeat manipulations. There are two versions, for mono (bbcutm) or stereo (bbcuts) sources. Whilst originally based on breakbeat cutting, the opcode can be applied to any type of source audio.

a1,a2  bbcuts  asource1, asource2, ibps, isubdiv, ibarlength, iphrasebars, \
          inumrepeats [, istutterspeed] [, istutterchance] [, ienvchoice]

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

flooper :: Sig -> Sig -> D -> D -> D -> Tab -> Sig Source

Function-table-based crossfading looper.

This opcode reads audio from a function table and plays it back in a loop with user-defined start time, duration and crossfade time. It also allows the pitch of the loop to be controlled, including reversed playback. It accepts non-power-of-two tables, such as deferred-allocation GEN01 tables.

asig  flooper  kamp, kpitch, istart, idur, ifad, ifn

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

flooper2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Function-table-based crossfading looper.

This opcode implements a crossfading looper with variable loop parameters and three looping modes, optionally using a table for its crossfade shape. It accepts non-power-of-two tables for its source sounds, such as deferred-allocation GEN01 tables.

asig  flooper2  kamp, kpitch, kloopstart, kloopend, kcrossfade, ifn \
          [, istart, imode, ifenv, iskip]

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

fluidAllOut :: (Sig, Sig) Source

Collects all audio from all Fluidsynth engines in a performance

aleft, aright  fluidAllOut  

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

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

Sends a MIDI controller data message to fluid.

Sends a MIDI controller data (MIDI controller number and value to use) message to a fluid engine by number on the user specified MIDI channel number.

 fluidCCi  iEngineNumber, iChannelNumber, iControllerNumber, iValue

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

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

Sends a MIDI controller data message to fluid.

Sends a MIDI controller data (MIDI controller number and value to use) message to a fluid engine by number on the user specified MIDI channel number.

 fluidCCk  iEngineNumber, iChannelNumber, iControllerNumber, kValue

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

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

Sends MIDI note on, note off, and other messages to a SoundFont preset.

The fluid opcodes provide a simple Csound opcode wrapper around Peter Hanappe's Fluidsynth SoundFont2 synthesizer. This implementation accepts any MIDI note on, note off, controller, pitch bend, or program change message at k-rate. Maximum polyphony is 4096 simultaneously sounding voices. Any number of SoundFonts may be loaded and played simultaneously.

 fluidControl  ienginenum, kstatus, kchannel, kdata1, kdata2

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

fluidEngine :: D Source

Instantiates a fluidsynth engine.

Instantiates a fluidsynth engine, and returns ienginenum to identify the engine. ienginenum is passed to other other opcodes for loading and playing SoundFonts and gathering the generated sound.

ienginenum  fluidEngine  [iReverbEnabled] [, iChorusEnabled] [,iNumChannels] [, iPolyphony] 

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

fluidLoad :: D -> D -> Tab Source

Loads a SoundFont into a fluidEngine, optionally listing SoundFont contents.

Loads a SoundFont into an instance of a fluidEngine, optionally listing banks and presets for SoundFont.

isfnum  fluidLoad  soundfont, ienginenum[, ilistpresets]

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

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

Plays a note on a channel in a fluidSynth engine.

Plays a note at imidikey pitch and imidivel velocity on ichannelnum channel of number ienginenum fluidEngine.

 fluidNote  ienginenum, ichannelnum, imidikey, imidivel

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

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

Outputs sound from a given fluidEngine

Outputs the sound from a fluidEngine.

aleft, aright  fluidOut  ienginenum

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

fluidProgramSelect :: D -> D -> Tab -> D -> D -> SE () Source

Assigns a preset from a SoundFont to a channel on a fluidEngine.

 fluidProgramSelect  ienginenum, ichannelnum, isfnum, ibanknum, ipresetnum

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

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

Set interpolation method for channel in Fluid Engine

Set interpolation method for channel in Fluid Engine. Lower order interpolation methods will render faster at lower fidelity while higher order interpolation methods will render slower at higher fidelity. Default interpolation for a channel is 4th order interpolation.

 fluidSetInterpMethod  ienginenum, ichannelnum, iInterpMethod

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

loscil :: Tuple a => Sig -> Sig -> Tab -> a Source

Read sampled sound from a table.

Read sampled sound (mono or stereo) from a table, with optional sustain and release looping.

ar1 [,ar2]  loscil  xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] \
          [, imod2] [, ibeg2] [, iend2]

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

loscil3 :: Tuple a => Sig -> Sig -> Tab -> a Source

Read sampled sound from a table using cubic interpolation.

Read sampled sound (mono or stereo) from a table, with optional sustain and release looping, using cubic interpolation.

ar1 [,ar2]  loscil3  xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] \
          [, imod2] [, ibeg2] [, iend2]

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

loscilx :: Tuple a => Sig -> Sig -> Tab -> a Source

Loop oscillator.

This file is currently a stub, but the syntax should be correct.

ar1 [, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, ar13, ar14, \
          ar15, ar16]  loscilx  xamp, kcps, ifn \
          [, iwsize, ibas, istrt, imod1, ibeg1, iend1]

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

lphasor :: Sig -> Sig Source

Generates a table index for sample playback

This opcode can be used to generate table index for sample playback (e.g. tablexkt).

ares  lphasor  xtrns [, ilps] [, ilpe] [, imode] [, istrt] [, istor]

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

lposcil :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Read sampled sound from a table with looping and high precision.

Read sampled sound (mono or stereo) from a table, with looping, and high precision.

ares  lposcil  kamp, kfreqratio, kloop, kend, ifn [, iphs]

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

lposcil3 :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Read sampled sound from a table with high precision and cubic interpolation.

Read sampled sound (mono or stereo) from a table, with looping, and high precision. lposcil3 uses cubic interpolation.

ares  lposcil3  kamp, kfreqratio, kloop, kend, ifn [, iphs]

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

lposcila :: Sig -> Sig -> Sig -> Sig -> D -> Sig Source

Read sampled sound from a table with looping and high precision.

lposcila reads sampled sound from a table with looping and high precision.

ar  lposcila  aamp, kfreqratio, kloop, kend, ift [,iphs] 

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

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

Read stereo sampled sound from a table with looping and high precision.

lposcilsa reads stereo sampled sound from a table with looping and high precision.

ar1, ar2  lposcilsa  aamp, kfreqratio, kloop, kend, ift [,iphs] 

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

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

Read stereo sampled sound from a table with looping and high precision.

lposcilsa2 reads stereo sampled sound from a table with looping and high precision.

ar1, ar2  lposcilsa2  aamp, kfreqratio, kloop, kend, ift [,iphs] 

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

sfilist :: Sf -> SE () Source

Prints a list of all instruments of a previously loaded SoundFont2 (SF2) file.

Prints a list of all instruments of a previously loaded SoundFont2 (SF2) sample file. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

 sfilist  ifilhandle

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

sfinstr :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig) Source

Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound.

Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ar1, ar2  sfinstr  ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \
          [, iflag] [, ioffset]

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

sfinstr3 :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig) Source

Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound with cubic interpolation.

Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ar1, ar2  sfinstr3  ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \
          [, iflag] [, ioffset]

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

sfinstr3m :: D -> D -> Sig -> Sig -> D -> Sf -> Sig Source

Plays a SoundFont2 (SF2) sample instrument, generating a mono sound with cubic interpolation.

Plays a SoundFont2 (SF2) sample instrument, generating a mono sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ares  sfinstr3m  ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \
          [, iflag] [, ioffset]

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

sfinstrm :: D -> D -> Sig -> Sig -> D -> Sf -> Sig Source

Plays a SoundFont2 (SF2) sample instrument, generating a mono sound.

Plays a SoundFont2 (SF2) sample instrument, generating a mono sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ares  sfinstrm  ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \
          [, iflag] [, ioffset]

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

sfload :: Str -> D Source

Loads an entire SoundFont2 (SF2) sample file into memory.

Loads an entire SoundFont2 (SF2) sample file into memory. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ir  sfload  "filename"

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

sflooper :: D -> D -> Sig -> Sig -> Sf -> Sig -> Sig -> Sig -> (Sig, Sig) Source

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound, with user-defined time-varying crossfade looping.

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound, similarly to sfplay. Unlike that opcode, though, it ignores the looping points set in the SF2 file and substitutes them for a user-defined crossfade loop. It is a cross between sfplay and flooper2.

ar1, ar2  sflooper  ivel, inotenum, kamp, kpitch, ipreindex, kloopstart, kloopend, kcrossfade \
          [, istart, imode, ifenv, iskip] 

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

sfpassign :: D -> Sf -> SE () Source

Assigns all presets of a SoundFont2 (SF2) sample file to a sequence of progressive index numbers.

Assigns all presets of a previously loaded SoundFont2 (SF2) sample file to a sequence of progressive index numbers. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

 sfpassign  istartindex, ifilhandle[, imsgs]

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

sfplay :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig) Source

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound.

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ar1, ar2  sfplay  ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]

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

sfplay3 :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig) Source

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound with cubic interpolation.

Plays a SoundFont2 (SF2) sample preset, generating a stereo sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ar1, ar2  sfplay3  ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]

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

sfplay3m :: D -> D -> Sig -> Sig -> Sf -> Sig Source

Plays a SoundFont2 (SF2) sample preset, generating a mono sound with cubic interpolation.

Plays a SoundFont2 (SF2) sample preset, generating a mono sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ares  sfplay3m  ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]

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

sfplaym :: D -> D -> Sig -> Sig -> Sf -> Sig Source

Plays a SoundFont2 (SF2) sample preset, generating a mono sound.

Plays a SoundFont2 (SF2) sample preset, generating a mono sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ares  sfplaym  ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]

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

sfplist :: Sf -> SE () Source

Prints a list of all presets of a SoundFont2 (SF2) sample file.

Prints a list of all presets of a previously loaded SoundFont2 (SF2) sample file. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

 sfplist  ifilhandle

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

sfpreset :: D -> D -> Sf -> Sf -> D Source

Assigns an existing preset of a SoundFont2 (SF2) sample file to an index number.

Assigns an existing preset of a previously loaded SoundFont2 (SF2) sample file to an index number. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.

ir  sfpreset  iprog, ibank, ifilhandle, ipreindex

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

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

A sound looper with pitch control.

This opcode records input audio and plays it back in a loop with user-defined duration and crossfade time. It also allows the pitch of the loop to be controlled, including reversed playback.

asig, krec  sndloop  ain, kpitch, ktrig, idur, ifad

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

waveset :: Sig -> Sig -> Sig Source

A simple time stretch by repeating cycles.

ares  waveset  ain, krep [, ilen]

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

Scanned Synthesis.

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

Copies from one table to another with a gain control.

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.

 scanhammer  isrc, idst, ipos, imult

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

scans :: Sig -> Sig -> Tab -> D -> Sig Source

Generate audio output using scanned synthesis.

ares  scans  kamp, kfreq, ifn, id [, iorder]

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

scantable :: Sig -> Sig -> D -> D -> D -> D -> D -> Sig Source

A simpler scanned synthesis implementation.

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.

aout  scantable  kamp, kpch, ipos, imass, istiff, idamp, ivel

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

scanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE () Source

Compute the waveform and the wavetable for use in scanned synthesis.

 scanu  init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, \
          kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id

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

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

Allows the position and velocity of a node in a scanned process to be read.

kpos, kvel  xscanmap  iscan, kamp, kvamp [, iwhich]

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

xscans :: Sig -> Sig -> Tab -> D -> Sig Source

Fast scanned synthesis waveform and the wavetable generator.

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.

ares  xscans  kamp, kfreq, ifntraj, id [, iorder]

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

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

Allows the position and velocity of a node in a scanned process to be read.

 xscansmap  kpos, kvel, iscan, kamp, kvamp [, iwhich]

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

xscanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE () Source

Compute the waveform and the wavetable for use in scanned synthesis.

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.

 xscanu  init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, \
          kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id

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

STK Opcodes.

stkBandedWG :: D -> D -> Sig Source

STKBandedWG uses banded waveguide techniques to model a variety of sounds.

This opcode uses banded waveguide techniques to model a variety of sounds, including bowed bars, glasses, and bowls.

asignal  STKBandedWG  ifrequency, iamplitude, [kpress, kv1[, kmot, kv2[, klfo, kv3[, klfodepth, kv4[, kvel, kv5[, kstrk, kv6[, kinstr, kv7]]]]]]]

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

stkBeeThree :: D -> D -> Sig Source

STK Hammond-oid organ-like FM synthesis instrument.

asignal  STKBeeThree  ifrequency, iamplitude, [kop4, kv1[, kop3, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkBlowBotl :: D -> D -> Sig Source

STKBlowBotl uses a helmholtz resonator (biquad filter) with a polynomial jet excitation.

This opcode implements a helmholtz resonator (biquad filter) with a polynomial jet excitation (a la Cook).

asignal  STKBlowBotl  ifrequency, iamplitude, [knoise, kv1[, klfo, kv2[, klfodepth, kv3[, kvol, kv4]]]]

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

stkBlowHole :: D -> D -> Sig Source

STK clarinet physical model with one register hole and one tonehole.

This opcode is based on the clarinet model, with the addition of a two-port register hole and a three-port dynamic tonehole implementation.

asignal  STKBlowHole  ifrequency, iamplitude, [kreed, kv1[, knoise, kv2[, khole, kv3[, kreg, kv4[, kbreath, kv5]]]]]

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

stkBowed :: D -> D -> Sig Source

STKBowed is a bowed string instrument.

STKBowed is a bowed string instrument, using a waveguide model.

asignal  STKBowed  ifrequency, iamplitude, [kpress, kv1[, kpos, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]

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

stkBrass :: D -> D -> Sig Source

STKBrass is a simple brass instrument.

STKBrass uses a simple brass instrument waveguide model, a la Cook.

asignal  STKBrass  ifrequency, iamplitude, [klip, kv1[, kslide, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]

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

stkClarinet :: D -> D -> Sig Source

STKClarinet uses a simple clarinet physical model.

asignal  STKClarinet  ifrequency, iamplitude, [kstiff, kv1[, knoise, kv2[, klfo, kv3[, klfodepth, kv4[, kbreath, kv5]]]]]

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

stkDrummer :: D -> D -> Sig Source

STKDrummer is a drum sampling synthesizer.

STKDrummer is a drum sampling synthesizer using raw waves and one-pole filters, The drum rawwave files are sampled at 22050 Hz, but will be appropriately interpolated for other sample rates.

asignal  STKDrummer  ifrequency, iamplitude

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

stkFMVoices :: D -> D -> Sig Source

STKFMVoices is a singing FM synthesis instrument.

STKFMVoices is a singing FM synthesis instrument. It has 3 carriers and a common modulator, also referred to as algorithm 6 of the TX81Z.

asignal  STKFMVoices  ifrequency, iamplitude, [kvowel, kv1[, kspec, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkFlute :: D -> D -> Sig Source

STKFlute uses a simple flute physical model.

STKFlute uses a simple flute physical model. The jet model uses a polynomial, a la Cook.

asignal  STKFlute  ifrequency, iamplitude, [kjet, kv1[, knoise, kv2[, klfo, kv3[, klfodepth, kv4[, kbreath, kv5]]]]]

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

stkHevyMetl :: D -> D -> Sig Source

STKHevyMetl produces metal sounds.

STKHevyMetl produces metal sounds, using FM synthesis. It uses 3 cascade operators with feedback modulation, also referred to as algorithm 3 of the TX81Z.

asignal  STKHevyMetl  ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkMandolin :: D -> D -> Sig Source

STKMandolin produces mamdolin-like sounds.

STKMandolin produces mamdolin-like sounds, using "commuted synthesis" techniques to model a mandolin instrument.

asignal  STKMandolin  ifrequency, iamplitude, [kbody, kv1[, kpos, kv2[, ksus, kv3[, kdetune, kv4[, kmic, kv5]]]]]

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

stkModalBar :: D -> D -> Sig Source

STKModalBar is a resonant bar instrument.

This opcode is a resonant bar instrument.It has a number of different struck bar instruments.

asignal  STKModalBar  ifrequency, iamplitude, [khard, kv1[, kpos, kv2[, klfo, kv3[, klfodepth, kv4[, kmix, kv5[, kvol, kv6[, kinstr, kv7]]]]]]]

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

stkMoog :: D -> D -> Sig Source

STKMoog produces moog-like swept filter sounds.

STKMoog produces moog-like swept filter sounds, using one attack wave, one looped wave, and an ADSR envelope and adds two sweepable formant filters.

asignal  STKMoog  ifrequency, iamplitude, [kq, kv1[, krate, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]

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

stkPercFlut :: D -> D -> Sig Source

STKPercFlut is a percussive flute FM synthesis instrument.

STKPercFlut is a percussive flute FM synthesis instrument. The instrument uses an algorithm like the algorithm 4 of the TX81Z.

asignal  STKPercFlut  ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkPlucked :: D -> D -> Sig Source

STKPlucked uses a plucked string physical model.

STKPlucked uses a plucked string physical model based on the Karplus-Strong algorithm.

asignal  STKPlucked  ifrequency, iamplitude

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

stkResonate :: D -> D -> Sig Source

STKResonate is a noise driven formant filter.

STKResonate is a noise driven formant filter. This instrument contains a noise source, which excites a biquad resonance filter, with volume controlled by an ADSR.

asignal  STKResonate  ifrequency, iamplitude, [kfreq, kv1[, kpole, kv2[, knotch, kv3[, kzero, kv4[, kenv, kv5]]]]]

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

stkRhodey :: D -> D -> Sig Source

STK Fender Rhodes-like electric piano FM synthesis instrument.

asignal  STKRhodey  ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkSaxofony :: D -> D -> Sig Source

STKSaxofony is a faux conical bore reed instrument.

STKSaxofony is a faux conical bore reed instrument. This opcode uses a "hybrid" digital waveguide instrument that can generate a variety of wind-like sounds. It has also been referred to as the "blowed string" model. The waveguide section is essentially that of a string, with one rigid and one lossy termination. The non-linear function is a reed table. The string can be "blown" at any point between the terminations, though just as with strings, it is impossible to excite the system at either end. If the excitation is placed at the string mid-point, the sound is that of a clarinet. At points closer to the "bridge", the sound is closer to that of a saxophone.

asignal  STKSaxofony  ifrequency, iamplitude, [kstiff, kv1[, kapert, kv2[, kblow, kv3[, knoise, kv4[, klfo, kv5[, klfodepth, kv6[, kbreath, kv7]]]]]]]

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

stkShakers :: D -> D -> Sig Source

STKShakers is an instrument that simulates environmental sounds or collisions of multiple independent sound producing objects.

STKShakers are a set of PhISEM and PhOLIES instruments: PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects. It can simulate a Maraca, Sekere, Cabasa, Bamboo Wind Chimes, Water Drops, Tambourine, Sleighbells, and a Guiro. On http://soundlab.cs.princeton.edu/research/controllers/shakers/ PhOLIES (Physically-Oriented Library of Imitated Environmental Sounds) there is a similar approach for the synthesis of environmental sounds. It simulates of breaking sticks, crunchy snow (or not), a wrench, sandpaper, and more..

asignal  STKShakers  ifrequency, iamplitude, [kenerg, kv1[, kdecay, kv2[, kshake, kv3[, knum, kv4[, kres, kv5[, kinstr, kv6]]]]]]

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

stkSimple :: D -> D -> Sig Source

STKSimple is a wavetable/noise instrument.

STKSimple is a wavetable/noise instrument. It combines a looped wave, a noise source, a biquad resonance filter, a one-pole filter, and an ADSR envelope to create some interesting sounds.

asignal  STKSimple  ifrequency, iamplitude, [kpos, kv1[, kcross, kv2[, kenv, kv3[, kgain, kv4]]]]

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

stkSitar :: D -> D -> Sig Source

STKSitar uses a plucked string physical model.

STKSitar uses a plucked string physical model based on the Karplus-Strong algorithm.

asignal  STKSitar  ifrequency, iamplitude

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

stkStifKarp :: D -> D -> Sig Source

STKStifKarp is a plucked stiff string instrument.

STKStifKarp is a plucked stiff string instrument. It a simple plucked string algorithm (Karplus Strong) with enhancements, including string stiffness and pluck position controls. The stiffness is modeled with allpass filters.

asignal  STKStifKarp  ifrequency, iamplitude, [kpos, kv1[, ksus, kv2[, kstretch, kv3]]]

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

stkTubeBell :: D -> D -> Sig Source

STKTubeBell is a tubular bell (orchestral chime) FM synthesis instrument.

STKTubeBell is a tubular bell (orchestral chime) FM synthesis instrument. It uses two simple FM Pairs summed together, also referred to as algorithm 5 of the TX81Z.

asignal  STKTubeBell  ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

stkVoicForm :: D -> D -> Sig Source

STKVoicForm is a four formant synthesis instrument.

STKVoicForm is a four formant synthesis instrument. This instrument contains an excitation singing wavetable (looping wave with random and periodic vibrato, smoothing on frequency, etc.), excitation noise, and four sweepable complex resonances. Measured formant data is included, and enough data is there to support either parallel or cascade synthesis. In the floating point case cascade synthesis is the most natural so that's what you'll find here.

asignal  STKVoicForm  ifrequency, iamplitude, [kmix, kv1[, ksel, kv2[, klfo, kv3[, klfodepth, kv4[, kloud, kv5]]]]]

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

stkWhistle :: D -> D -> Sig Source

STKWhistle produces whistle sounds.

STKWhistle produces (police) whistle sounds. It uses a hybrid physical/spectral model of a police whistle (a la Cook).

asignal  STKWhistle  ifrequency, iamplitude, [kmod, kv1[, knoise, kv2[, kfipfreq, kv3[, kfipgain, kv4[, kvol, kv5]]]]]

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

stkWurley :: D -> D -> Sig Source

STKWurley simulates a Wurlitzer electric piano FM synthesis instrument.

STKWurley simulates a Wurlitzer electric piano FM synthesis instrument. It uses two simple FM Pairs summed together, also referred to as algorithm 5 of the TX81Z.

asignal  STKWurley  ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]

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

Table Access.

oscil1 :: D -> Sig -> D -> Sig Source

Accesses table values by incremental sampling.

kres  oscil1  idel, kamp, idur [, ifn]

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

oscil1i :: D -> Sig -> D -> Sig Source

Accesses table values by incremental sampling with linear interpolation.

kres  oscil1i  idel, kamp, idur [, ifn]

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

ptable :: Sig -> Tab -> Sig Source

Accesses table values by direct indexing.

ares  ptable  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  ptable  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  ptable  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

ptable3 :: Sig -> Tab -> Sig Source

Accesses table values by direct indexing with cubic interpolation.

ares  ptable3  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  ptable3  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  ptable3  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

ptablei :: Sig -> Tab -> Sig Source

Accesses table values by direct indexing with linear interpolation.

ares  ptablei  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  ptablei  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  ptablei  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

tab_i :: D -> Tab -> D Source

Fast table opcodes.

Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).

ir  tab_i  indx, ifn[, ixmode]

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

tab :: Sig -> Tab -> Sig Source

Fast table opcodes.

Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).

kr  tab  kndx, ifn[, ixmode]
ar  tab  xndx, ifn[, ixmode]

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

tabw_i :: D -> D -> Tab -> SE () Source

Fast table opcodes.

Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).

 tabw_i  isig, indx, ifn [,ixmode]

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

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

Fast table opcodes.

Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).

 tabw  ksig, kndx, ifn [,ixmode]
 tabw  asig, andx, ifn [,ixmode]

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

table :: SigOrD a => a -> Tab -> a Source

Accesses table values by direct indexing.

ares  table  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  table  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  table  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

table3 :: SigOrD a => a -> Tab -> a Source

Accesses table values by direct indexing with cubic interpolation.

ares  table3  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  table3  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  table3  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

tablei :: SigOrD a => a -> Tab -> a Source

Accesses table values by direct indexing with linear interpolation.

ares  tablei  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  tablei  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  tablei  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

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

Wave Terrain Synthesis.

wterrain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig Source

A simple wave-terrain synthesis opcode.

aout  wterrain  kamp, kpch, k_xcenter, k_ycenter, k_xradius, k_yradius, \
          itabx, itaby

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

Waveguide Physical Modeling.

pluck :: Sig -> Sig -> D -> Tab -> D -> Sig Source

Produces a naturally decaying plucked string or drum sound.

Audio output is a naturally decaying plucked string or drum sound based on the Karplus-Strong algorithms.

ares  pluck  kamp, kcps, icps, ifn, imeth [, iparm1] [, iparm2]

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

repluck :: D -> Sig -> D -> Sig -> Sig -> Sig -> Sig Source

Physical model of the plucked string.

repluck is an implementation of the physical model of the plucked string. A user can control the pluck point, the pickup point, the filter, and an additional audio signal, axcite. axcite is used to excite the string. Based on the Karplus-Strong algorithm.

ares  repluck  iplk, kamp, icps, kpick, krefl, axcite

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

streson :: Sig -> Sig -> D -> Sig Source

A string resonator with variable fundamental frequency.

An audio signal is modified by a string resonator with variable fundamental frequency.

ares  streson  asig, kfr, ifdbgain

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

wgbow :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig Source

Creates a tone similar to a bowed string.

Audio output is a tone similar to a bowed string, using a physical model developed from Perry Cook, but re-coded for Csound.

ares  wgbow  kamp, kfreq, kpres, krat, kvibf, kvamp, ifn [, iminfreq]

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

wgbowedbar :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

A physical model of a bowed bar.

A physical model of a bowed bar, belonging to the Perry Cook family of waveguide instruments.

ares  wgbowedbar  kamp, kfreq, kpos, kbowpres, kgain [, iconst] [, itvel] \
          [, ibowpos] [, ilow]

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

wgbrass :: Sig -> Sig -> Sig -> D -> Sig -> Sig -> Tab -> Sig Source

Creates a tone related to a brass instrument.

Audio output is a tone related to a brass instrument, using a physical model developed from Perry Cook, but re-coded for Csound.

ares  wgbrass  kamp, kfreq, ktens, iatt, kvibf, kvamp, ifn [, iminfreq]

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

wgclar :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Tab -> Sig Source

Creates a tone similar to a clarinet.

Audio output is a tone similar to a clarinet, using a physical model developed from Perry Cook, but re-coded for Csound.

ares  wgclar  kamp, kfreq, kstiff, iatt, idetk, kngain, kvibf, kvamp, ifn \
          [, iminfreq]

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

wgflute :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Tab -> Sig Source

Creates a tone similar to a flute.

Audio output is a tone similar to a flute, using a physical model developed from Perry Cook, but re-coded for Csound.

ares  wgflute  kamp, kfreq, kjet, iatt, idetk, kngain, kvibf, kvamp, ifn \
          [, iminfreq] [, ijetrf] [, iendrf]

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

wgpluck :: D -> D -> Sig -> D -> D -> D -> Sig -> Sig Source

A high fidelity simulation of a plucked string.

A high fidelity simulation of a plucked string, using interpolating delay-lines.

ares  wgpluck  icps, iamp, kpick, iplk, idamp, ifilt, axcite

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

wgpluck2 :: D -> Sig -> D -> Sig -> Sig -> Sig Source

Physical model of the plucked string.

wgpluck2 is an implementation of the physical model of the plucked string, with control over the pluck point, the pickup point and the filter. Based on the Karplus-Strong algorithm.

ares  wgpluck2  iplk, kamp, icps, kpick, krefl

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