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

Safe HaskellNone
LanguageHaskell98

Csound.Typed.Opcode.SpectralProcessing

Contents

Synopsis

STFT.

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

Deprecated.

Deprecated. Use the tableseg opcode instead.

 ktableseg  ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]

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

pvadd :: Sig -> Sig -> Str -> Tab -> D -> Sig Source

Reads from a pvoc file and uses the data to perform additive synthesis.

pvadd reads from a pvoc file and uses the data to perform additive synthesis using an internal array of interpolating oscillators. The user supplies the wave table (usually one period of a sine wave), and can choose which analysis bins will be used in the re-synthesis.

ares  pvadd  ktimpnt, kfmod, ifilcod, ifn, ibins [, ibinoffset] \
          [, ibinincr] [, iextractmode] [, ifreqlim] [, igatefn]

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

pvbufread :: Sig -> Str -> SE () Source

Reads from a phase vocoder analysis file and makes the retrieved data available.

pvbufread reads from a pvoc file and makes the retrieved data available to any following pvinterp and pvcross units that appear in an instrument before a subsequent pvbufread (just as lpread and lpreson work together). The data is passed internally and the unit has no output of its own.

 pvbufread  ktimpnt, ifile

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

pvcross :: Sig -> Sig -> Str -> Sig -> Sig -> Sig Source

Applies the amplitudes from one phase vocoder analysis file to the data from a second file.

pvcross applies the amplitudes from one phase vocoder analysis file to the data from a second file and then performs the resynthesis. The data is passed, as described above, from a previously called pvbufread unit. The two k-rate amplitude arguments are used to scale the amplitudes of each files separately before they are added together and used in the resynthesis (see below for further explanation). The frequencies of the first file are not used at all in this process. This unit simply allows for cross-synthesis through the application of the amplitudes of the spectra of one signal to the frequencies of a second signal. Unlike pvinterp, pvcross does allow for the use of the ispecwp as in pvoc and vpvoc.

ares  pvcross  ktimpnt, kfmod, ifile, kampscale1, kampscale2 [, ispecwp]

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

pvinterp :: Sig -> Sig -> Str -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source

Interpolates between the amplitudes and frequencies of two phase vocoder analysis files.

pvinterp interpolates between the amplitudes and frequencies, on a bin by bin basis, of two phase vocoder analysis files (one from a previously called pvbufread unit and the other from within its own argument list), allowing for user defined transitions between analyzed sounds. It also allows for general scaling of the amplitudes and frequencies of each file separately before the interpolated values are calculated and sent to the resynthesis routines. The kfmod argument in pvinterp performs its frequency scaling on the frequency values after their derivation from the separate scaling and subsequent interpolation is performed so that this acts as an overall scaling value of the new frequency components.

ares  pvinterp  ktimpnt, kfmod, ifile, kfreqscale1, kfreqscale2, \
          kampscale1, kampscale2, kfreqinterp, kampinterp

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

pvoc :: Sig -> Sig -> Str -> Sig Source

Implements signal reconstruction using an fft-based phase vocoder.

ares  pvoc  ktimpnt, kfmod, ifilcod [, ispecwp] [, iextractmode] \
          [, ifreqlim] [, igatefn]

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

pvread :: Sig -> Str -> D -> (Sig, Sig) Source

Reads from a phase vocoder analysis file and returns the frequency and amplitude from a single analysis channel or bin.

pvread reads from a pvoc file and returns the frequency and amplitude from a single analysis channel or bin. The returned values can be used anywhere else in the Csound instrument. For example, one can use them as arguments to an oscillator to synthesize a single component from an analyzed signal or a bank of pvreads can be used to resynthesize the analyzed sound using additive synthesis by passing the frequency and magnitude values to a bank of oscillators.

kfreq, kamp  pvread  ktimpnt, ifile, ibin

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

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

Creates a new function table by making linear segments between values in stored function tables.

tableseg is like linseg but interpolate between values in a stored function tables. The result is a new function table passed internally to any following vpvoc which occurs before a subsequent tableseg (much like lpread/lpreson pairs work). The uses of these are described below under vpvoc.

 tableseg  ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]

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

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

Creates a new function table by making exponential segments between values in stored function tables.

tablexseg is like expseg but interpolate between values in a stored function tables. The result is a new function table passed internally to any following vpvoc which occurs before a subsequent tablexseg (much like lpread/lpreson pairs work). The uses of these are described below under vpvoc.

 tablexseg  ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]

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

vpvoc :: Sig -> Sig -> Str -> Sig Source

Implements signal reconstruction using an fft-based phase vocoder and an extra envelope.

ares  vpvoc  ktimpnt, kfmod, ifile [, ispecwp] [, ifn]

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

LPC.

lpfreson :: Sig -> Sig -> Sig Source

Resynthesises a signal from the data passed internally by a previous lpread, applying formant shifting.

ares  lpfreson  asig, kfrqratio

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

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

Computes a new set of poles from the interpolation between two analysis.

 lpinterp  islot1, islot2, kmix

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

lpread :: Sig -> Str -> (Sig, Sig, Sig, Sig) Source

Reads a control file of time-ordered information frames.

krmsr, krmso, kerr, kcps  lpread  ktimpnt, ifilcod [, inpoles] [, ifrmrate]

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

lpreson :: Sig -> Sig Source

Resynthesises a signal from the data passed internally by a previous lpread.

ares  lpreson  asig

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

lpslot :: D -> SE () Source

Selects the slot to be use by further lp opcodes.

 lpslot  islot

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

Non-Standard.

specaddm :: Wspec -> Wspec -> Wspec Source

Perform a weighted add of two input spectra.

wsig  specaddm  wsig1, wsig2 [, imul2]

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

specdiff :: Wspec -> Wspec Source

Finds the positive difference values between consecutive spectral frames.

wsig  specdiff  wsigin

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

specdisp :: Wspec -> D -> SE () Source

Displays the magnitude values of the spectrum.

 specdisp  wsig, iprd [, iwtflg]

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

specfilt :: Wspec -> D -> Wspec Source

Filters each channel of an input spectrum.

wsig  specfilt  wsigin, ifhtim

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

spechist :: Wspec -> Wspec Source

Accumulates the values of successive spectral frames.

wsig  spechist  wsigin

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

specptrk :: Wspec -> Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig) Source

Estimates the pitch of the most prominent complex tone in the spectrum.

Estimate the pitch of the most prominent complex tone in the spectrum.

koct, kamp  specptrk  wsig, kvar, ilo, ihi, istr, idbthresh, inptls, \
          irolloff [, iodd] [, iconfs] [, interp] [, ifprd] [, iwtflg]

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

specscal :: Wspec -> D -> D -> Wspec Source

Scales an input spectral datablock with spectral envelopes.

wsig  specscal  wsigin, ifscale, ifthresh

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

specsum :: Wspec -> Sig Source

Sums the magnitudes across all channels of the spectrum.

ksum  specsum  wsig [, interp]

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

spectrum :: Sig -> D -> D -> D -> Wspec Source

Generate a constant-Q, exponentially-spaced DFT.

Generate a constant-Q, exponentially-spaced DFT across all octaves of a multiply-downsampled control or audio input signal.

wsig  spectrum  xsig, iprd, iocts, ifrqa [, iq] [, ihann] [, idbout] \
          [, idsprd] [, idsinrs]

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

Streaming.

binit :: Spec -> D -> Spec Source

PVS tracks to amplitude+frequency conversion.

The binit opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and converts it into a equal-bandwidth bin-frame containing amplitude and frequency pairs (PVS_AMP_FREQ), suitable for overlap-add resynthesis (such as performed by pvsynth) or further PVS streaming phase vocoder signal transformations. For each frequency bin, it will look for a suitable track signal to fill it; if not found, the bin will be empty (0 amplitude). If more than one track fits a certain bin, the one with highest amplitude will be chosen. This means that not all of the input signal is actually binned, the operation is lossy. However, in many situations this loss is not perceptually relevant.

fsig  binit  fin, isize

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

partials :: Spec -> Spec -> Sig -> Sig -> Sig -> D -> Spec Source

Partial track spectral analysis.

The partials opcode takes two input PV streaming signals containg AMP_FREQ and AMP_PHASE signals (as generated for instance by pvsifd or in the first case, by pvsanal) and performs partial track analysis, as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It generates a TRACKS PV streaming signal, containing amplitude, frequency, phase and track ID for each output track. This type of signal will contain a variable number of output tracks, up to the total number of analysis bins contained in the inputs (fftsize/2 + 1 bins). The second input (AMP_PHASE) is optional, as it can take the same signal as the first input. In this case, however, all phase information will be NULL and resynthesis using phase information cannot be performed.

ftrks  partials  ffr, fphs, kthresh, kminpts, kmaxgap, imaxtracks

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

pvsadsyn :: Spec -> D -> Sig -> Sig Source

Resynthesize using a fast oscillator-bank.

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

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

pvsanal :: Sig -> D -> D -> D -> D -> Spec Source

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

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

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

pvsarp :: Spec -> Sig -> Sig -> Sig -> Spec Source

Arpeggiate the spectral components of a streaming pv signal.

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

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

pvsbandp :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec Source

A band pass filter working in the spectral domain.

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]

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

pvsbandr :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec Source

A band reject filter working in the spectral domain.

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]

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

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

Obtain the amp and freq values off a PVS signal bin.

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

kamp, kfr  pvsbin  fsig, kbin

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

pvsblur :: Spec -> Sig -> D -> Spec Source

Average the amp/freq time functions of each analysis channel for a specified time.

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

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

pvsbuffer :: Spec -> D -> (D, Sig) Source

This opcode creates and writes to a circular buffer for f-signals (streaming PV signals).

This opcode sets up and writes to a circular buffer of length ilen (secs), giving a handle for the buffer and a time pointer, which holds the current write position (also in seconds). It can be used with one or more pvsbufread opcodes. Writing is circular, wrapping around at the end of the buffer.

ihandle, ktime   pvsbuffer  fsig, ilen 

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

pvsbufread :: Sig -> Sig -> Spec Source

This opcode reads a circular buffer of f-signals (streaming PV signals).

This opcode reads from a circular buffer of length ilen (secs), taking a handle for the buffer and a time pointer, which holds the current read position (also in seconds). It is used in conjunction with a pvsbuffer opocde. Reading is circular, wrapping around at the end of the buffer.

fsig  pvsbufread   ktime, khandle[, ilo, ihi, iclear] 

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

pvsbufread2 :: Sig -> Sig -> D -> D -> Spec Source

This opcode reads a circular buffer of f-signals (streaming PV signals), with binwise additional delays.

This opcode reads from a circular buffer of length ilen (secs), taking a handle for the buffer and a time pointer, which holds the current read position (also in seconds). It is used in conjunction with a pvsbuffer opocde. Reading is circular, wrapping around at the end of the buffer. Extra delay times are taken from a function table, with each point on it defining a delay time in seconds affecting the corresponding bin.

fsig  pvsbufread2   ktime, khandle, ift1, ift2 

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

pvscale :: Spec -> Sig -> Spec Source

Scale the frequency components of a pv stream.

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]

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

pvscent :: Spec -> Sig Source

Calculate the spectral centroid of a signal.

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

kcent  pvscent  fsig

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

pvscross :: Spec -> Spec -> Sig -> Sig -> Spec Source

Performs cross-synthesis between two source fsigs.

fsig  pvscross  fsrc, fdest, kamp1, kamp2

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

pvsdemix :: Spec -> Spec -> Sig -> Sig -> D -> Spec Source

Spectral azimuth-based de-mixing of stereo sources.

Spectral azimuth-based de-mixing of stereo sources, with a reverse-panning result. This opcode implements the Azimuth Discrimination and Resynthesis (ADRess) algorithm, developed by Dan Barry (Barry et Al. "Sound Source Separation Azimuth Discrimination and Resynthesis". DAFx'04, Univ. of Napoli). The source separation, or de-mixing, is controlled by two parameters: an azimuth position (kpos) and a subspace width (kwidth). The first one is used to locate the spectral peaks of individual sources on a stereo mix, whereas the second widens the 'search space', including/exclufing the peaks around kpos. These two parameters can be used interactively to extract source sounds from a stereo mix. The algorithm is particularly successful with studio recordings where individual instruments occupy individual panning positions; it is, in fact, a reverse-panning algorithm.

fsig  pvsdemix  fleft, fright, kpos, kwidth, ipoints

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

pvsdiskin :: Str -> Sig -> Sig -> Spec Source

Read a selected channel from a PVOC-EX analysis file.

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]

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

pvsdisp :: Spec -> SE () Source

Displays a PVS signal as an amplitude vs. freq graph.

This opcode will display a PVS signal fsig. Uses X11 or FLTK windows if enabled, else (or if -g flag is set) displays are approximated in ASCII characters.

 pvsdisp  fsig[, ibins, iwtflg] 

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

pvsfilter :: Spec -> Spec -> Sig -> Spec Source

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

fsig  pvsfilter  fsigin, fsigfil, kdepth[, igain]

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

pvsfread :: Sig -> Tab -> Spec Source

Read a selected channel from a PVOC-EX analysis file.

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]

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

pvsfreeze :: Spec -> Sig -> Sig -> Spec Source

Freeze the amplitude and frequency time functions of a pv stream according to a control-rate trigger.

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

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

pvsftr :: Spec -> Tab -> SE () Source

Reads amplitude and/or frequency data from function tables.

 pvsftr  fsrc, ifna [, ifnf]

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

pvsftw :: Spec -> Tab -> Sig Source

Writes amplitude and/or frequency data to function tables.

kflag  pvsftw  fsrc, ifna [, ifnf]

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

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

Write a fsig to a PVOCEX file.

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

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

pvsgain :: Spec -> Sig -> Spec Source

Scale the amplitude of a pv stream.

fsig  pvsgain  fsigin, kgain 

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

pvshift :: Spec -> Sig -> Sig -> Spec Source

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

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

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

pvsifd :: Sig -> D -> D -> D -> (Spec, Spec) Source

Instantaneous Frequency Distribution, magnitude and phase analysis.

The pvsifd opcode takes an input a-rate signal and performs an Instantaneous Frequency, magnitude and phase analysis, using the STFT and pvsifd (Instantaneous Frequency Distribution), as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It generates two PV streaming signals, one containing the amplitudes and frequencies (a similar output to pvsanal) and another containing amplitudes and unwrapped phases.

ffr,fphs  pvsifd  ain, ifftsize, ihopsize, iwintype[,iscal]

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

pvsin :: Sig -> Spec Source

Retrieve an fsig from the input software bus; a pvs equivalent to chani.

This opcode retrieves an f-sig from the pvs in software bus, which can be used to get data from an external source, using the Csound 5 API. A channel is created if not already existing. The fsig channel is in that case initialised with the given parameters. It is important to note that the pvs input and output (pvsout opcode) busses are independent and data is not shared between them.

fsig  pvsin  kchan[, isize, iolap, iwinsize, iwintype, iformat]

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

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

Get information from a PVOC-EX formatted 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

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

pvsinit :: D -> Spec Source

Initialise a spectral (f) variable to zero.

Performs the equivalent to an init operation on an f-variable.

fsig  pvsinit  isize[, iolap, iwinsize, iwintype, iformat]

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

pvslock :: Spec -> Sig -> Spec Source

Frequency lock an input fsig

This opcode searches for spectral peaks and then locks the frequencies around those peaks. This is similar to phase-locking in non-streaming PV processing. It can be used to improve timestretching and pitch-shifting quality in PV processing.

fsig  pvslock  fsigin, klock

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

pvsmaska :: Spec -> Tab -> Sig -> Spec Source

Modify amplitudes using a function table, with dynamic scaling.

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

fsig  pvsmaska  fsrc, ifn, kdepth

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

pvsmix :: Spec -> Spec -> Spec Source

Mix seamlessly two pv signals.

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

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

pvsmooth :: Spec -> Sig -> Sig -> Spec Source

Smooth the amplitude and frequency time functions of a pv stream using parallel 1st order lowpass IIR filters with time-varying cutoff frequency.

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.

fsig  pvsmooth  fsigin, kacf, kfcf

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

pvsmorph :: Spec -> Spec -> Sig -> Sig -> Spec Source

Performs morphing (or interpolation) between two source fsigs.

Performs morphing (or interpolation) between two source fsigs.

fsig  pvsmorph  fsig1, fsig2, kampint, kfrqint

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

pvsosc :: Sig -> Sig -> Sig -> D -> Spec Source

PVS-based oscillator simulator.

Generates periodic signal spectra in AMP-FREQ format, with the option of four wave types:

fsig  pvsosc  kamp, kfreq, ktype, isize [,ioverlap] [, iwinsize] [, iwintype] [, iformat]

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

pvsout :: Spec -> Sig -> SE () Source

Write a fsig to the pvs output bus.

This opcode writes a fsig to a channel of the pvs output bus. Note that the pvs out bus and the pvs in bus are separate and independent. A new channel is created if non-existent.

 pvsout  fsig, kchan

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

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

Track the pitch and amplitude of a PVS signal.

Track the pitch and amplitude of a PVS signal as k-rate variables.

kfr, kamp  pvspitch  fsig, kthresh

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

pvstencil :: Spec -> Sig -> Sig -> D -> Spec Source

Transforms a pvoc stream according to a masking function table.

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.

fsig  pvstencil  fsigin, kgain, klevel, iftable

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

pvsvoc :: Spec -> Spec -> Sig -> Sig -> Spec Source

Combine the spectral envelope of one fsig with the excitation (frequencies) of another.

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]

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

pvswarp :: Spec -> Sig -> Sig -> Spec Source

Warp the spectral envelope of a PVS signal

Warp the spectral envelope of a PVS signal by means of shifting and scaling.

fsig  pvswarp  fsigin, kscal, kshift[, klowest, kmeth, kgain, kcoefs]

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

pvsynth :: Spec -> Sig Source

Resynthesise using a FFT overlap-add.

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

ares  pvsynth  fsrc, [iinit]

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

resyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig Source

Streaming partial track additive synthesis with cubic phase interpolation with pitch control and support for timescale-modified input

The resyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials). It resynthesises the signal using linear amplitude and cubic phase interpolation to drive a bank of interpolating oscillators with amplitude and pitch scaling controls. Resyn is a modified version of sinsyn, allowing for the resynthesis of data with pitch and timescale changes.

asig  resyn  fin, kscal, kpitch, kmaxtracks, ifn

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

sinsyn :: Spec -> Sig -> Sig -> Tab -> Sig Source

Streaming partial track additive synthesis with cubic phase interpolation

The sinsyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by the partials opcode). It resynthesises the signal using linear amplitude and cubic phase interpolation to drive a bank of interpolating oscillators with amplitude scaling control. sinsyn attempts to preserve the phase of the partials in the original signal and in so doing it does not allow for pitch or timescale modifications of the signal.

asig  sinsyn  fin, kscal, kmaxtracks, ifn

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

tradsyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig Source

Streaming partial track additive synthesis

The tradsyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials),as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It resynthesises the signal using linear amplitude and frequency interpolation to drive a bank of interpolating oscillators with amplitude and pitch scaling controls.

asig  tradsyn  fin, kscal, kpitch, kmaxtracks, ifn

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

trcross :: Spec -> Spec -> Sig -> Sig -> Spec Source

Streaming partial track cross-synthesis.

The trcross opcode takes two inputs containg TRACKS pv streaming signals (as generated, for instance by partials) and cross-synthesises them into a single TRACKS stream. Two different modes of operation are used: mode 0, cross-synthesis by multiplication of the amplitudes of the two inputs and mode 1, cross-synthesis by the substititution of the amplitudes of input 1 by the input 2. Frequencies and phases of input 1 are preserved in the output. The cross-synthesis is done by matching tracks between the two inputs using a 'search interval'. The matching algorithm will look for tracks in the second input that are within the search interval around each track in the first input. This interval can be changed at the control rate. Wider search intervals will find more matches.

fsig  trcross  fin1, fin2, ksearch, kdepth [, kmode] 

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

trfilter :: Spec -> Sig -> Tab -> Spec Source

Streaming partial track filtering.

The trfilter opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and filters it using an amplitude response curve stored in a function table. The function table can have any size (no restriction to powers-of-two). The table lookup is done by linear-interpolation. It is possible to create time-varying filter curves by updating the amlitude response table with a table-writing opcode.

fsig  trfilter  fin, kamnt, ifn

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

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

Extracts the highest-frequency track from a streaming track input signal.

The trhighest opcode takes an input containg TRACKS pv streaming signals (as generated, for instance by partials) and outputs only the highest track. In addition it outputs two k-rate signals, corresponding to the frequency and amplitude of the highest track signal.

fsig, kfr, kamp  trhighest  fin1, kscal

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

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

Extracts the lowest-frequency track from a streaming track input signal.

The trlowest opcode takes an input containg TRACKS pv streaming signals (as generated, for instance by partials) and outputs only the lowest track. In addition it outputs two k-rate signals, corresponding to the frequency and amplitude of the lowest track signal.

fsig, kfr, kamp  trlowest  fin1, kscal

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

trmix :: Spec -> Spec -> Spec Source

Streaming partial track mixing.

The trmix opcode takes two inputs containg TRACKS pv streaming signals (as generated, for instance by partials) and mixes them into a single TRACKS stream. Tracks will be mixed up to the available space (defined by the original number of FFT bins in the analysed signals). If the sum of the input tracks exceeds this space, the higher-ordered tracks in the second input will be pruned.

fsig  trmix  fin1, fin2 

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

trscale :: Spec -> Sig -> Spec Source

Streaming partial track frequency scaling.

The trscale opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and scales all frequencies by a k-rate amount. It can also, optionally, scale the gain of the signal by a k-rate amount (default 1). The result is pitch shifting of the input tracks.

fsig  trscale  fin, kpitch[, kgain]

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

trshift :: Spec -> Sig -> Spec Source

Streaming partial track frequency scaling.

The trshift opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and shifts all frequencies by a k-rate frequency. It can also, optionally, scale the gain of the signal by a k-rate amount (default 1). The result is frequency shifting of the input tracks.

fsig  trshift  fin, kpshift[, kgain]

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

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

Streaming partial track frequency splitting.

The trsplit opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and splits it into two signals according to a k-rate frequency 'split point'. The first output will contain all tracks up from 0Hz to the split frequency and the second will contain the tracks from the split frequency up to the Nyquist. It can also, optionally, scale the gain of the output signals by a k-rate amount (default 1). The result is two output signals containing only part of the original spectrum.

fsiglow, fsighi  trsplit  fin, ksplit[, kgainlow, kgainhigh]

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

ATS.

atsAdd :: Sig -> Sig -> D -> Tab -> D -> Sig Source

uses the data from an ATS analysis file to perform additive synthesis.

ATSadd reads from an ATS analysis file and uses the data to perform additive synthesis using an internal array of interpolating oscillators.

ar  ATSadd  ktimepnt, kfmod, iatsfile, ifn, ipartials[, ipartialoffset, \
            ipartialincr, igatefn]

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

atsAddnz :: Sig -> D -> D -> Sig Source

uses the data from an ATS analysis file to perform noise resynthesis.

ATSaddnz reads from an ATS analysis file and uses the data to perform additive synthesis using a modified randi function.

ar  ATSaddnz  ktimepnt, iatsfile, ibands[, ibandoffset, ibandincr]

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

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

reads data from and ATS data file and stores it in an internal data table of frequency, amplitude pairs.

ATSbufread reads data from and ATS data file and stores it in an internal data table of frequency, amplitude pairs.

 ATSbufread  ktimepnt, kfmod, iatsfile, ipartials[, ipartialoffset, \
              ipartialincr]

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

atsCross :: Sig -> Sig -> D -> Tab -> Sig -> Sig -> D -> Sig Source

perform cross synthesis from ATS analysis files.

ATScross uses data from an ATS analysis file and data from an ATSbufread to perform cross synthesis.

ar  ATScross  ktimepnt, kfmod, iatsfile, ifn, kmylev, kbuflev, ipartials \
              [, ipartialoffset, ipartialincr]

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

atsInfo :: D -> D -> D Source

reads data out of the header of an ATS file.

atsinfo reads data out of the header of an ATS file.

idata  ATSinfo  iatsfile, ilocation

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

atsInterpread :: Sig -> Sig Source

allows a user to determine the frequency envelope of any ATSbufread.

ATSinterpread allows a user to determine the frequency envelope of any ATSbufread.

kamp  ATSinterpread  kfreq

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

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

returns a frequency, amplitude pair from an ATSbufread opcode.

ATSpartialtap takes a partial number and returns a frequency, amplitude pair. The frequency and amplitude data comes from an ATSbufread opcode.

kfrq, kamp  ATSpartialtap  ipartialnum

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

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

reads data from an ATS file.

ATSread returns the amplitude (kamp) and frequency (kfreq) information of a user specified partial contained in the ATS analysis file at the time indicated by the time pointer ktimepnt.

kfreq, kamp  ATSread  ktimepnt, iatsfile, ipartial

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

atsReadnz :: Sig -> D -> D -> Sig Source

reads data from an ATS file.

ATSreadnz returns the energy (kenergy) of a user specified noise band (1-25 bands) at the time indicated by the time pointer ktimepnt.

kenergy  ATSreadnz  ktimepnt, iatsfile, iband

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

atsSinnoi :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig Source

uses the data from an ATS analysis file to perform resynthesis.

ATSsinnoi reads data from an ATS data file and uses the information to synthesize sines and noise together.

ar  ATSsinnoi  ktimepnt, ksinlev, knzlev, kfmod, iatsfile, ipartials \
              [, ipartialoffset, ipartialincr]

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

Loris.

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

Morphs two stored sets of bandwidth-enhanced partials and stores a new set of partials representing the morphed sound. The morph is performed by linearly interpolating the parameter envelopes (frequency, amplitude, and bandwidth, or noisiness) of the bandwidth-enhanced partials according to control-rate frequency, amplitude, and bandwidth morphing functions.

lorismorph morphs two stored sets of bandwidth-enhanced partials and stores a new set of partials representing the morphed sound. The morph is performed by linearly interpolating the parameter envelopes (frequency, amplitude, and bandwidth, or noisiness) of the bandwidth-enhanced partials according to control-rate frequency, amplitude, and bandwidth morphing functions.

 lorismorph  isrcidx, itgtidx, istoreidx, kfreqmorphenv, kampmorphenv, kbwmorphenv

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

lorisplay :: D -> Sig -> Sig -> Sig -> Sig Source

renders a stored set of bandwidth-enhanced partials using the method of Bandwidth-Enhanced Additive Synthesis implemented in the Loris software, applying control-rate frequency, amplitude, and bandwidth scaling envelopes.

lorisplay renders a stored set of bandwidth-enhanced partials using the method of Bandwidth-Enhanced Additive Synthesis implemented in the Loris software, applying control-rate frequency, amplitude, and bandwidth scaling envelopes.

ar  lorisplay  ireadidx, kfreqenv, kampenv, kbwenv

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

lorisread :: Sig -> Str -> D -> Sig -> Sig -> Sig -> SE () Source

Imports a set of bandwidth-enhanced partials from a SDIF-format data file, applying control-rate frequency, amplitude, and bandwidth scaling envelopes, and stores the modified partials in memory.

lorisread imports a set of bandwidth-enhanced partials from a SDIF-format data file, applying control-rate frequency, amplitude, and bandwidth scaling envelopes, and stores the modified partials in memory.

 lorisread  ktimpnt, ifilcod, istoreidx, kfreqenv, kampenv, kbwenv[, ifadetime]

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