csound-expression-1.0.3: library to make electronic music

Safe HaskellSafe-Inferred

Csound.Opcode.Advanced

Contents

Description

Advanced Signal Processing

Synopsis

Modulation and Distortion

Frequency Modulation

foscil :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> SigSource

A basic frequency modulated oscillator.

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

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

foscili :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> SigSource

Basic frequency modulated oscillator with linear interpolation.

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

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

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

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

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

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

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

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

Distortion and Wave Shaping

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

Distort an audio signal via waveshaping and optional clipping.

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

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

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

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

          exp(asig * (shape1 + pregain)) - exp(asig * (shape2 - pregain))
   aout = ---------------------------------------------------------------
          exp(asig * pregain)            + exp(-asig * pregain)
 ares distort1 asig, kpregain, kpostgain, kshape1, kshape2[, imode]

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

powershape :: Sig -> Sig -> SigSource

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

 aout powershape ain, kShapeAmount [, ifullscale]

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

polynomial :: Sig -> [Sig] -> SigSource

The polynomial opcode calculates a polynomial with a single a-rate input variable. The polynomial is a sum of any number of terms in the form kn*x^n where kn is the nth coefficient of the expression. These coefficients are k-rate values.

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

doc: http://www.csounds.com/manual/html/polynomial.html

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

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

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

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

Flanging, Phasing, Phase Shaping

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

A user controlled flanger.

 ares flanger asig, adel, kfeedback [, imaxd]

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

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

Analyze an audio input and generate harmonizing voices in synchrony.

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

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

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

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

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

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

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

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

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

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

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

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

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

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

pdhalf :: Sig -> Sig -> Sig -> SigSource

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

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

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

pdhalfy :: Sig -> Sig -> Sig -> SigSource

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

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

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

Doppler Shift

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

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

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

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

Granular Synthesis

fof :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> SigSource

Audio output is a succession of sinusoid bursts initiated at frequency xfund with a spectral peak at xform. For xfund above 25 Hz these burts 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.

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

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

Convolution

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

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

  • small delay
  • possible to run in real-time for shorter impulse files
  • no pre-process analysis pass
  • can often render faster than convolve
 ar1 [, ar2] [, ar3] [, ar4] pconvolve ain, ifilcod [, ipartitionsize, ichannel]

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

convolve :: CsdTuple a => Sig -> D -> aSource

Output is the convolution of signal ain and the impulse response contained in ifilcod. If more than one output signal is supplied, each will be convolved with the same impulse response. Note that it is considerably more efficient to use one instance of the operator when processing a mono input to create stereo, or quad, outputs.

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

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

ftconv :: CsdTuple a => Sig -> Tab -> D -> aSource

Low latency multichannel convolution, using a function table as impulse response source. The algorithm is to split the impulse response to partitions of length determined by the iplen parameter, and delay and mix partitions so that the original, full length impulse response is reconstructed without gaps. The output delay (latency) is iplen samples, and does not depend on the control rate, unlike in the case of other convolve opcodes.

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

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

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

A direct convolution opcode.

 ares dconv asig, isize, ifn

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

FFT and Spectral Processing

Realtime Analysis And Resynthesis

pvsanal :: Sig -> D -> D -> D -> D -> SpecSource

Generate an fsig from a mono audio source ain, using phase vocoder overlap-add analysis.

 fsig pvsanal ain, ifftsize, ioverlap, iwinsize, iwintype [, iformat] [, iinit]

doc: http://www.csounds.com/manual/html/pvsanal.html

pvstanal :: Sig -> Sig -> Sig -> Sig -> SpecSource

pvstanal implements phase vocoder analysis by reading function tables containing sampled-sound sources, with GEN01, and pvstanal will accept deferred allocation tables.

This opcode allows for time and frequency-independent scaling. Time is advanced internally, but controlled by a tempo scaling parameter; when an onset is detected, timescaling is momentarily stopped to avoid smearing of attacks. The quality of the effect is generally improved with phase locking switched on.

pvstanal will also scale pitch, independently of frequency, using a transposition factor (k-rate).

 fsig pvstanal ktimescal, kamp, kpitch, ktab, [kdetect, kwrap, ioffset,ifftsize, ihop, idbthresh]

doc: http://www.csounds.com/manual/html/pvstanal.html

pvsynth :: Spec -> SigSource

Resynthesise phase vocoder data (f-signal) using a FFT overlap-add.

 ares pvsynth fsrc, [iinit]

doc: http://www.csounds.com/manual/html/pvsynth.html

pvsadsyn :: Spec -> D -> Sig -> SigSource

Resynthesize using a fast oscillator-bank.

 ares pvsadsyn fsrc, inoscs, kfmod [, ibinoffset] [, ibinincr] [, iinit]

doc: http://www.csounds.com/manual/html/pvsadsyn.html

Writing FFT Data To A File And Reading From It

pvswrite :: Spec -> Str -> SE ()Source

This opcode writes a fsig to a PVOCEX file (which in turn can be read by pvsfread or other programs that support PVOCEX file input).

 pvsfwrite fsig, ifile

doc: http://www.csounds.com/manual/html/pvsfwrite.html

pvsfread :: Sig -> Str -> SpecSource

Create an fsig stream by reading a selected channel from a PVOC-EX analysis file loaded into memory, with frame interpolation. Only format 0 files (amplitude+frequency) are currently supported. The operation of this opcode mirrors that of pvoc, but outputs an fsig instead of a resynthesized signal.

 fsig pvsfread ktimpt, ifn [, ichan]

doc: http://www.csounds.com/manual/html/pvsfread.html

pvsdiskin :: Str -> Sig -> Sig -> SpecSource

Create an fsig stream by reading a selected channel from a PVOC-EX analysis file, with frame interpolation.

 fsig pvsdiskin SFname,ktscal,kgain[,ioffset, ichan]

doc: http://www.csounds.com/manual/html/pvsdiskin.html

FFT Info

pvsinfo :: Spec -> (D, D, D, D)Source

Get format information about fsrc, whether created by an opcode such as pvsanal, or obtained from a PVOCEX file by pvsfread. This information is available at init time, and can be used to set parameters for other pvs opcodes, and in particular for creating function tables (e.g. for pvsftw), or setting the number of oscillators for pvsadsyn.

 ioverlap, inumbins, iwinsize, iformat pvsinfo fsrc

doc: http://www.csounds.com/manual/html/pvsinfo.html

pvsbin :: Spec -> Sig -> (Sig, Sig)Source

Obtain the amp and freq values off a PVS signal bin as k-rate variables.

 kamp, kfr pvsbin fsig, kbin

doc: http://www.csounds.com/manual/html/pvsbin.html

pvscent :: Spec -> SigSource

Calculate the spectral centroid of a signal from its discrete Fourier transform.

 kcent pvscent fsig

doc: http://www.csounds.com/manual/html/pvscent.html

Manipulating FFT Signals

pvscale :: Spec -> Sig -> SpecSource

Scale the frequency components of a pv stream, resulting in pitch shift. Output amplitudes can be optionally modified in order to attempt formant preservation.

 fsig pvscale fsigin, kscal[, kkeepform, kgain, kcoefs]

doc: http://www.csounds.com/manual/html/pvscale.html

pvshift :: Spec -> Sig -> Sig -> SpecSource

Shift the frequency components of a pv stream, stretching/compressing its spectrum.

 fsig pvshift fsigin, kshift, klowest[, kkeepform, igain, kcoefs]

doc: http://www.csounds.com/manual/html/pvshift.html

pvsbandp :: Spec -> Sig -> Sig -> Sig -> Sig -> SpecSource

Filter the pvoc frames, passing bins whose frequency is within a band, and with linear interpolation for transitional bands.

 fsig pvsbandp fsigin, xlowcut, xlowfull, \
       xhighfull, xhighcut[, ktype]

doc: http://www.csounds.com/manual/html/pvsbandp.html

pvsbandr :: Spec -> Sig -> Sig -> Sig -> Sig -> SpecSource

Filter the pvoc frames, rejecting bins whose frequency is within a band, and with linear interpolation for transitional bands.

 fsig pvsbandr fsigin, xlowcut, xlowfull, \
       xhighfull, xhighcut[, ktype]

doc: http://www.csounds.com/manual/html/pvsbandr.html

pvsmix :: Spec -> Spec -> SpecSource

Mix seamlessly two pv signals. This opcode combines the most prominent components of two pvoc streams into a single mixed stream.

 fsig pvsmix fsigin1, fsigin2

doc: http://www.csounds.com/manual/html/pvsmix.html

pvscross :: Spec -> Spec -> Sig -> Sig -> SpecSource

Performs cross-synthesis between two source fsigs.

 fsig pvscross fsrc, fdest, kamp1, kamp2

doc: http://www.csounds.com/manual/html/pvscross.html

pvsfilter :: Spec -> Spec -> Sig -> SpecSource

Multiply amplitudes of a pvoc stream by those of a second pvoc stream, with dynamic scaling.

 fsig pvsfilter fsigin, fsigfil, kdepth[, igain]

doc: http://www.csounds.com/manual/html/pvsfilter.html

pvsvoc :: Spec -> Spec -> Sig -> Sig -> SpecSource

This opcode provides support for cross-synthesis of amplitudes and frequencies. It takes the amplitudes of one input fsig and combines with frequencies from another. It is a spectral version of the well-known channel vocoder.

 fsig pvsvoc famp, fexc, kdepth, kgain [,kcoefs]

doc: http://www.csounds.com/manual/html/pvsvoc.html

pvsmorph :: Spec -> Spec -> Sig -> Sig -> SpecSource

Performs morphing (or interpolation) between two source fsigs.

 fsig pvsmorph fsrc, fdest, kamp1, kamp2

doc: http://www.csounds.com/manual/html/pvsmotph.html

pvsfreeze :: Spec -> Sig -> Sig -> SigSource

This opcodes freezes the evolution of pvs stream by locking into steady amplitude and/or frequency values for each bin. The freezing is controlled, independently for amplitudes and frequencies, by a control-rate trigger, which switches the freezing on if equal to or above 1 and off if below 1.

 fsig pvsfreeze fsigin, kfreeza, kfreezf

doc: http://www.csounds.com/manual/html/pvsfreeze.html

pvsmaska :: Spec -> Tab -> Sig -> SpecSource

Modify amplitudes of fsrc using function table, with dynamic scaling.

 fsig pvsmaska fsrc, ifn, kdepth

doc: http://www.csounds.com/manual/html/pvsmaska.html

pvsblur :: Spec -> Sig -> D -> SpecSource

Average the amp/freq time functions of each analysis channel for a specified time (truncated to number of frames). As a side-effect the input pvoc stream will be delayed by that amount.

 fsig pvsblur fsigin, kblurtime, imaxdel

doc: http://www.csounds.com/manual/html/pvsblur.html

pvstencil :: Spec -> Sig -> Sig -> Tab -> SigSource

Transforms a pvoc stream according to a masking function table; if the pvoc stream amplitude falls below the value of the function for a specific pvoc channel, it applies a gain to that channel.

The pvoc stream amplitudes are compared to a masking table, if the fall below the table values, they are scaled by kgain. Prior to the operation, table values are scaled by klevel, which can be used as masking depth control.

Tables have to be at least fftsize/2 in size; for most GENS it is important to use an extended-guard point (size power-of-two plus one), however this is not necessary with GEN43.

One of the typical uses of pvstencil would be in noise reduction. A noise print can be analysed with pvanal into a PVOC-EX file and loaded in a table with GEN43. This then can be used as the masking table for pvstencil and the amount of reduction would be controlled by kgain. Skipping post-normalisation will keep the original noise print average amplitudes. This would provide a good starting point for a successful noise reduction (so that klevel can be generally set to close to 1).

Other possible transformation effects are possible, such as filtering and `inverse-masking'.

 fsig pvstencil fsigin, kgain, klevel, iftable

doc: http://www.csounds.com/manual/html/pvstencil.html

pvsarp :: Spec -> Sig -> Sig -> Sig -> SpecSource

This opcode arpeggiates spectral components, by amplifying one bin and attenuating all the others around it. Used with an LFO it will provide a spectral arpeggiator similar to Trevor Wishart's CDP program specarp.

 fsig pvsarp fsigin, kbin, kdepth, kgain

doc: http://www.csounds.com/manual/html/pvsarp.html

pvsmooth :: Spec -> Sig -> Sig -> SpecSource

Smooth the amplitude and frequency time functions of a pv stream using a 1st order lowpass IIR with time-varying cutoff frequency. This opcode uses the same filter as the tone opcode, but this time acting separately on the amplitude and frequency time functions that make up a pv stream. The cutoff frequency parameter runs at the control-rate, but unlike tone and tonek, it is not specified in Hz, but as fractions of 1/2 frame-rate (actually the pv stream sampling rate), which is easier to understand. This means that the highest cutoff frequency is 1 and the lowest 0; the lower the frequency the smoother the functions and more pronounced the effect will be.

These are filters applied to control signals so the effect is basically blurring the spectral evolution. The effects produced are more or less similar to pvsblur, but with two important differences: 1.smoothing of amplitudes and frequencies use separate sets of filters; and 2. there is no increase in computational cost when higher amounts of blurring (smoothing) are desired.

 fsig pvsmooth fsigin, kacf, kfcf

doc: http://www.csounds.com/manual/html/pvsmooth.html

Physical Models and FM Instruments

Waveguide Physical Modelling

streson :: Sig -> Sig -> D -> SigSource

An audio signal is modified by a string resonator with variable fundamental frequency.

 ares streson asig, kfr, ifdbgain

doc: http://www.csounds.com/manual/html/streson.html

pluck :: Sig -> Sig -> D -> Tab -> D -> SigSource

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]     

doc: http://www.csounds.com/manual/html/pluck.html

repluck :: D -> Sig -> D -> Sig -> Sig -> Sig -> SigSource

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

doc: http://www.csounds.com/manual/html/repluck.html

wgbow :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> SigSource

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]

doc: http://www.csounds.com/manual/html/wgbow.html

wgbowedbar :: Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

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]

doc: http://www.csounds.com/manual/html/wgbowedbar.html

wgbrass :: Sig -> Sig -> Sig -> D -> Sig -> Sig -> Tab -> SigSource

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]   

doc: http://www.csounds.com/manual/html/wgbrass.html

wgclar :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Tab -> SigSource

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]

doc: http://www.csounds.com/manual/html/wgclar.html

wgflute :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Tab -> SigSource

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]

doc: http://www.csounds.com/manual/html/wgflute.html

wgpluck :: D -> D -> Sig -> D -> D -> D -> Sig -> SigSource

A high fidelity simulation of a plucked string, using interpolating delay-lines.

 ares wgpluck icps, iamp, kpick, iplk, idamp, ifilt, axcite

doc: http://www.csounds.com/manual/html/wgpluck.html

wgpluck2 :: D -> Sig -> D -> Sig -> Sig -> SigSource

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

doc: http://www.csounds.com/manual/html/wgpluck2.html

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

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

 ares wguide1 asig, xfreq, kcutoff, kfeedback

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

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

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

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

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

FM Instrument Models

fmb3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

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

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

fmbell :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

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]

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

fmmetal :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

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

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

fmpercfl :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

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

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

fmrhode :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

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

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

fmvoice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

FM Singing Voice Synthesis

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

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

fmwurlie :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> SigSource

PhISEM opcodes

PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.

bamboo :: Sig -> D -> SigSource

bamboo is a semi-physical model of a bamboo sound.

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

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

cabasa :: D -> D -> SigSource

cabasa is a semi-physical model of a cabasa sound.

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

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

crunch :: D -> D -> SigSource

crunch is a semi-physical model of a crunch sound.

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

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

dripwater :: Sig -> D -> SigSource

dripwater is a semi-physical model of a water drop.

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

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

guiro :: Sig -> D -> SigSource

guiro is a semi-physical model of a guiro sound.

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

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

sandpaper :: D -> D -> SigSource

sandpaper is a semi-physical model of a sandpaper sound.

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

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

sekere :: D -> D -> SigSource

sekere is a semi-physical model of a sekere sound.

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

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

sleighbells :: Sig -> D -> SigSource

sleighbells is a semi-physical model of a sleighbell sound.

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

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

stix :: D -> D -> SigSource

stix is a semi-physical model of a stick sound.

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

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

tambourine :: Sig -> D -> SigSource

tambourine is a semi-physical model of a tambourine sound.

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

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

Some Perry Cook's instruments

The method is a physically inspired model developed from Perry Cook, but re-coded for Csound.

gogobel :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> SigSource

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

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

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

marimba :: Sig -> Sig -> D -> D -> Tab -> Sig -> Sig -> Tab -> D -> SigSource

Audio output is a tone related to the striking of a wooden block as found in a marimba.

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

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

shaker :: Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Audio output is a tone related to the shaking of a maraca or similar gourd instrument.

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

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

vibes :: Sig -> Sig -> D -> D -> Tab -> Sig -> Sig -> Tab -> D -> SigSource

Audio output is a tone related to the striking of a metal block as found in a vibraphone.

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

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

Other Models

barmodel :: Sig -> Sig -> D -> D -> Sig -> D -> D -> D -> D -> SigSource

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

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

mandol :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> SigSource

An emulation of a mandolin.

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

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

moog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> SigSource

An emulation of a mini-Moog synthesizer.

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

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

voice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> SigSource

An emulation of a human voice.

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

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