module Csound.Typed.Opcode.SpectralProcessing ( -- * STFT. ktableseg, pvadd, pvbufread, pvcross, pvinterp, pvoc, pvread, tableseg, tablexseg, vpvoc, -- * LPC. lpfreson, lpinterp, lpread, lpreson, lpslot, -- * Non-Standard. specaddm, specdiff, specdisp, specfilt, spechist, specptrk, specscal, specsum, spectrum, -- * Streaming. binit, partials, pvsadsyn, pvsanal, pvsarp, pvsbandp, pvsbandr, pvsbin, pvsblur, pvsbuffer, pvsbufread, pvsbufread2, pvscale, pvscent, pvscross, pvsdemix, pvsdiskin, pvsdisp, pvsfilter, pvsfread, pvsfreeze, pvsftr, pvsftw, pvsfwrite, pvsgain, pvshift, pvsifd, pvsin, pvsinfo, pvsinit, pvslock, pvsmaska, pvsmix, pvsmooth, pvsmorph, pvsosc, pvsout, pvspitch, pvstencil, pvsvoc, pvswarp, pvsynth, resyn, sinsyn, tradsyn, trcross, trfilter, trhighest, trlowest, trmix, trscale, trshift, trsplit, -- * ATS. atsAdd, atsAddnz, atsBufread, atsCross, atsInfo, atsInterpread, atsPartialtap, atsRead, atsReadnz, atsSinnoi, -- * Loris. lorismorph, lorisplay, lorisread) where import Control.Applicative import Control.Monad.Trans.Class import Csound.Dynamic import Csound.Typed -- STFT. -- | -- Deprecated. -- -- Deprecated. Use the tableseg opcode instead. -- -- > ktableseg ifn1, idur1, ifn2 [, idur2] [, ifn3] [...] -- -- csound doc: ktableseg :: Tab -> D -> Tab -> SE () ktableseg b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unTab b1 <*> unD b2 <*> unTab b3 where f a1 a2 a3 = opcs "ktableseg" [(Xr,(repeat Ir))] [a1,a2,a3] -- | -- 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: pvadd :: Sig -> Sig -> Str -> Tab -> D -> Sig pvadd b1 b2 b3 b4 b5 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unStr b3 <*> unTab b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "pvadd" [(Ar,[Kr,Kr,Sr,Ir,Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: pvbufread :: Sig -> Str -> SE () pvbufread b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unStr b2 where f a1 a2 = opcs "pvbufread" [(Xr,[Kr,Sr])] [a1,a2] -- | -- 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: pvcross :: Sig -> Sig -> Str -> Sig -> Sig -> Sig pvcross b1 b2 b3 b4 b5 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unStr b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "pvcross" [(Ar,[Kr,Kr,Sr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: pvinterp :: Sig -> Sig -> Str -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig pvinterp b1 b2 b3 b4 b5 b6 b7 b8 b9 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unStr b3 <*> unSig b4 <*> unSig b5 <*> unSig b6 <*> unSig b7 <*> unSig b8 <*> unSig b9 where f a1 a2 a3 a4 a5 a6 a7 a8 a9 = opcs "pvinterp" [(Ar,[Kr,Kr,Sr,Kr,Kr,Kr,Kr,Kr,Kr])] [a1 ,a2 ,a3 ,a4 ,a5 ,a6 ,a7 ,a8 ,a9] -- | -- Implements signal reconstruction using an fft-based phase vocoder. -- -- > ares pvoc ktimpnt, kfmod, ifilcod [, ispecwp] [, iextractmode] \ -- > [, ifreqlim] [, igatefn] -- -- csound doc: pvoc :: Sig -> Sig -> Str -> Sig pvoc b1 b2 b3 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unStr b3 where f a1 a2 a3 = opcs "pvoc" [(Ar,[Kr,Kr,Sr,Ir,Ir,Ir,Ir])] [a1,a2,a3] -- | -- 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: pvread :: Tuple a => Sig -> Str -> D -> a pvread b1 b2 b3 = pureTuple $ f <$> unSig b1 <*> unStr b2 <*> unD b3 where f a1 a2 a3 = mopcs "pvread" ([Kr,Kr],[Kr,Sr,Ir]) [a1,a2,a3] -- | -- 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: tableseg :: Tab -> D -> Tab -> SE () tableseg b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unTab b1 <*> unD b2 <*> unTab b3 where f a1 a2 a3 = opcs "tableseg" [(Xr,(repeat Ir))] [a1,a2,a3] -- | -- 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: tablexseg :: Tab -> D -> Tab -> SE () tablexseg b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unTab b1 <*> unD b2 <*> unTab b3 where f a1 a2 a3 = opcs "tablexseg" [(Xr,(repeat Ir))] [a1,a2,a3] -- | -- Implements signal reconstruction using an fft-based phase vocoder and an extra envelope. -- -- > ares vpvoc ktimpnt, kfmod, ifile [, ispecwp] [, ifn] -- -- csound doc: vpvoc :: Sig -> Sig -> Str -> Sig vpvoc b1 b2 b3 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unStr b3 where f a1 a2 a3 = opcs "vpvoc" [(Ar,[Kr,Kr,Sr,Ir,Ir])] [a1,a2,a3] -- LPC. -- | -- Resynthesises a signal from the data passed internally by a previous lpread, applying formant shifting. -- -- > ares lpfreson asig, kfrqratio -- -- csound doc: lpfreson :: Sig -> Sig -> Sig lpfreson b1 b2 = Sig $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "lpfreson" [(Ar,[Ar,Kr])] [a1,a2] -- | -- Computes a new set of poles from the interpolation between two analysis. -- -- > lpinterp islot1, islot2, kmix -- -- csound doc: lpinterp :: D -> D -> Sig -> SE () lpinterp b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unSig b3 where f a1 a2 a3 = opcs "lpinterp" [(Xr,[Ir,Ir,Kr])] [a1,a2,a3] -- | -- Reads a control file of time-ordered information frames. -- -- > krmsr, krmso, kerr, kcps lpread ktimpnt, ifilcod [, inpoles] [, ifrmrate] -- -- csound doc: lpread :: Tuple a => Sig -> Str -> a lpread b1 b2 = pureTuple $ f <$> unSig b1 <*> unStr b2 where f a1 a2 = mopcs "lpread" ([Kr,Kr,Kr,Kr],[Kr,Sr,Ir,Ir]) [a1,a2] -- | -- Resynthesises a signal from the data passed internally by a previous lpread. -- -- > ares lpreson asig -- -- csound doc: lpreson :: Sig -> Sig lpreson b1 = Sig $ f <$> unSig b1 where f a1 = opcs "lpreson" [(Ar,[Ar])] [a1] -- | -- Selects the slot to be use by further lp opcodes. -- -- > lpslot islot -- -- csound doc: lpslot :: D -> SE () lpslot b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 where f a1 = opcs "lpslot" [(Xr,[Ir])] [a1] -- Non-Standard. -- | -- Perform a weighted add of two input spectra. -- -- > wsig specaddm wsig1, wsig2 [, imul2] -- -- csound doc: specaddm :: Wspec -> Wspec -> Wspec specaddm b1 b2 = Wspec $ f <$> unWspec b1 <*> unWspec b2 where f a1 a2 = opcs "specaddm" [(Wr,[Wr,Wr,Ir])] [a1,a2] -- | -- Finds the positive difference values between consecutive spectral frames. -- -- > wsig specdiff wsigin -- -- csound doc: specdiff :: Wspec -> Wspec specdiff b1 = Wspec $ f <$> unWspec b1 where f a1 = opcs "specdiff" [(Wr,[Wr])] [a1] -- | -- Displays the magnitude values of the spectrum. -- -- > specdisp wsig, iprd [, iwtflg] -- -- csound doc: specdisp :: Wspec -> D -> SE () specdisp b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unWspec b1 <*> unD b2 where f a1 a2 = opcs "specdisp" [(Xr,[Wr,Ir,Ir])] [a1,a2] -- | -- Filters each channel of an input spectrum. -- -- > wsig specfilt wsigin, ifhtim -- -- csound doc: specfilt :: Wspec -> D -> Wspec specfilt b1 b2 = Wspec $ f <$> unWspec b1 <*> unD b2 where f a1 a2 = opcs "specfilt" [(Wr,[Wr,Ir])] [a1,a2] -- | -- Accumulates the values of successive spectral frames. -- -- > wsig spechist wsigin -- -- csound doc: spechist :: Wspec -> Wspec spechist b1 = Wspec $ f <$> unWspec b1 where f a1 = opcs "spechist" [(Wr,[Wr])] [a1] -- | -- 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: specptrk :: Tuple a => Wspec -> Sig -> D -> D -> D -> D -> D -> D -> a specptrk b1 b2 b3 b4 b5 b6 b7 b8 = pureTuple $ f <$> unWspec b1 <*> unSig b2 <*> unD b3 <*> unD b4 <*> unD b5 <*> unD b6 <*> unD b7 <*> unD b8 where f a1 a2 a3 a4 a5 a6 a7 a8 = mopcs "specptrk" ([Kr,Kr] ,[Wr,Kr,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir]) [a1,a2,a3,a4,a5,a6,a7,a8] -- | -- Scales an input spectral datablock with spectral envelopes. -- -- > wsig specscal wsigin, ifscale, ifthresh -- -- csound doc: specscal :: Wspec -> D -> D -> Wspec specscal b1 b2 b3 = Wspec $ f <$> unWspec b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "specscal" [(Wr,[Wr,Ir,Ir])] [a1,a2,a3] -- | -- Sums the magnitudes across all channels of the spectrum. -- -- > ksum specsum wsig [, interp] -- -- csound doc: specsum :: Wspec -> Sig specsum b1 = Sig $ f <$> unWspec b1 where f a1 = opcs "specsum" [(Kr,[Wr,Ir])] [a1] -- | -- 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: spectrum :: Sig -> D -> D -> D -> Wspec spectrum b1 b2 b3 b4 = Wspec $ f <$> unSig b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "spectrum" [(Wr,[Xr,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- Streaming. -- | -- 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: binit :: Spec -> D -> Spec binit b1 b2 = Spec $ f <$> unSpec b1 <*> unD b2 where f a1 a2 = opcs "binit" [(Fr,[Fr,Ir])] [a1,a2] -- | -- 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: partials :: Spec -> Spec -> Sig -> Sig -> Sig -> D -> Spec partials b1 b2 b3 b4 b5 b6 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 <*> unD b6 where f a1 a2 a3 a4 a5 a6 = opcs "partials" [(Fr,[Fr,Fr,Kr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5,a6] -- | -- Resynthesize using a fast oscillator-bank. -- -- > ares pvsadsyn fsrc, inoscs, kfmod [, ibinoffset] [, ibinincr] [, iinit] -- -- csound doc: pvsadsyn :: Spec -> D -> Sig -> Sig pvsadsyn b1 b2 b3 = Sig $ f <$> unSpec b1 <*> unD b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsadsyn" [(Ar,[Fr,Ir,Kr,Ir,Ir,Ir])] [a1,a2,a3] -- | -- 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: pvsanal :: Sig -> D -> D -> D -> D -> Spec pvsanal b1 b2 b3 b4 b5 = Spec $ f <$> unSig b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "pvsanal" [(Fr,[Ar,Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: pvsarp :: Spec -> Sig -> Sig -> Sig -> Spec pvsarp b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "pvsarp" [(Fr,[Fr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: pvsbandp :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec pvsbandp b1 b2 b3 b4 b5 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "pvsbandp" [(Fr,[Fr,Xr,Xr,Xr,Xr,Kr])] [a1,a2,a3,a4,a5] -- | -- 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: pvsbandr :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec pvsbandr b1 b2 b3 b4 b5 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "pvsbandr" [(Fr,[Fr,Xr,Xr,Xr,Xr,Kr])] [a1,a2,a3,a4,a5] -- | -- 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: pvsbin :: Tuple a => Spec -> Sig -> a pvsbin b1 b2 = pureTuple $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = mopcs "pvsbin" ([Kr,Kr],[Fr,Kr]) [a1,a2] -- | -- 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: pvsblur :: Spec -> Sig -> D -> Spec pvsblur b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unD b3 where f a1 a2 a3 = opcs "pvsblur" [(Fr,[Fr,Kr,Ir])] [a1,a2,a3] -- | -- 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: pvsbuffer :: Tuple a => Spec -> D -> a pvsbuffer b1 b2 = pureTuple $ f <$> unSpec b1 <*> unD b2 where f a1 a2 = mopcs "pvsbuffer" ([Ir,Kr],[Fr,Ir]) [a1,a2] -- | -- 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: pvsbufread :: Sig -> Sig -> Spec pvsbufread b1 b2 = Spec $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "pvsbufread" [(Fr,[Kr,Kr,Ir,Ir,Ir])] [a1,a2] -- | -- 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: pvsbufread2 :: Sig -> Sig -> D -> D -> Spec pvsbufread2 b1 b2 b3 b4 = Spec $ f <$> unSig b1 <*> unSig b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "pvsbufread2" [(Fr,[Kr,Kr,Ir,Ir])] [a1,a2,a3,a4] -- | -- 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: pvscale :: Spec -> Sig -> Spec pvscale b1 b2 = Spec $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "pvscale" [(Fr,[Fr,Kr,Kr,Kr,Kr])] [a1,a2] -- | -- Calculate the spectral centroid of a signal. -- -- Calculate the spectral centroid of a signal from its discrete Fourier transform. -- -- > kcent pvscent fsig -- -- csound doc: pvscent :: Spec -> Sig pvscent b1 = Sig $ f <$> unSpec b1 where f a1 = opcs "pvscent" [(Kr,[Fr])] [a1] -- | -- Performs cross-synthesis between two source fsigs. -- -- > fsig pvscross fsrc, fdest, kamp1, kamp2 -- -- csound doc: pvscross :: Spec -> Spec -> Sig -> Sig -> Spec pvscross b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "pvscross" [(Fr,[Fr,Fr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: pvsdemix :: Spec -> Spec -> Sig -> Sig -> D -> Spec pvsdemix b1 b2 b3 b4 b5 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "pvsdemix" [(Fr,[Fr,Fr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: pvsdiskin :: Str -> Sig -> Sig -> Spec pvsdiskin b1 b2 b3 = Spec $ f <$> unStr b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsdiskin" [(Fr,[Sr,Kr,Kr,Ir,Ir])] [a1,a2,a3] -- | -- 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: pvsdisp :: Spec -> SE () pvsdisp b1 = SE $ (depT_ =<<) $ lift $ f <$> unSpec b1 where f a1 = opcs "pvsdisp" [(Xr,[Fr,Ir,Ir])] [a1] -- | -- Multiply amplitudes of a pvoc stream by those of a second -- pvoc stream, with dynamic scaling. -- -- > fsig pvsfilter fsigin, fsigfil, kdepth[, igain] -- -- csound doc: pvsfilter :: Spec -> Spec -> Sig -> Spec pvsfilter b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsfilter" [(Fr,[Fr,Fr,Kr,Ir])] [a1,a2,a3] -- | -- 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: pvsfread :: Sig -> Tab -> Spec pvsfread b1 b2 = Spec $ f <$> unSig b1 <*> unTab b2 where f a1 a2 = opcs "pvsfread" [(Fr,[Kr,Ir,Ir])] [a1,a2] -- | -- 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: pvsfreeze :: Spec -> Sig -> Sig -> Spec pvsfreeze b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsfreeze" [(Fr,[Fr,Kr,Kr])] [a1,a2,a3] -- | -- Reads amplitude and/or frequency data from function tables. -- -- > pvsftr fsrc, ifna [, ifnf] -- -- csound doc: pvsftr :: Spec -> Tab -> SE () pvsftr b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSpec b1 <*> unTab b2 where f a1 a2 = opcs "pvsftr" [(Xr,[Fr,Ir,Ir])] [a1,a2] -- | -- Writes amplitude and/or frequency data to function tables. -- -- > kflag pvsftw fsrc, ifna [, ifnf] -- -- csound doc: pvsftw :: Spec -> Tab -> Sig pvsftw b1 b2 = Sig $ f <$> unSpec b1 <*> unTab b2 where f a1 a2 = opcs "pvsftw" [(Kr,[Fr,Ir,Ir])] [a1,a2] -- | -- 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: pvsfwrite :: Spec -> Str -> SE () pvsfwrite b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSpec b1 <*> unStr b2 where f a1 a2 = opcs "pvsfwrite" [(Xr,[Fr,Sr])] [a1,a2] -- | -- Scale the amplitude of a pv stream. -- -- > fsig pvsgain fsigin, kgain -- -- csound doc: pvsgain :: Spec -> Sig -> Spec pvsgain b1 b2 = Spec $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "pvsgain" [(Fr,[Fr,Kr])] [a1,a2] -- | -- Shift the frequency components of a pv stream, stretching/compressing -- its spectrum. -- -- > fsig pvshift fsigin, kshift, klowest[, kkeepform, igain, kcoefs] -- -- csound doc: pvshift :: Spec -> Sig -> Sig -> Spec pvshift b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvshift" [(Fr,[Fr,Kr,Kr,Kr,Ir,Kr])] [a1,a2,a3] -- | -- 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: pvsifd :: Tuple a => Sig -> D -> D -> D -> a pvsifd b1 b2 b3 b4 = pureTuple $ f <$> unSig b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = mopcs "pvsifd" ([Fr,Fr],[Ar,Ir,Ir,Ir,Ir]) [a1,a2,a3,a4] -- | -- 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: pvsin :: Sig -> Spec pvsin b1 = Spec $ f <$> unSig b1 where f a1 = opcs "pvsin" [(Fr,[Kr,Ir,Ir,Ir,Ir,Ir])] [a1] -- | -- 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: pvsinfo :: Tuple a => Spec -> a pvsinfo b1 = pureTuple $ f <$> unSpec b1 where f a1 = mopcs "pvsinfo" ([Ir,Ir,Ir,Ir],[Fr]) [a1] -- | -- 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: pvsinit :: D -> Spec pvsinit b1 = Spec $ f <$> unD b1 where f a1 = opcs "pvsinit" [(Fr,[Ir,Ir,Ir,Ir,Ir])] [a1] -- | -- 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: pvslock :: Spec -> Sig -> Spec pvslock b1 b2 = Spec $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "pvslock" [(Fr,[Fr,Kr])] [a1,a2] -- | -- 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: pvsmaska :: Spec -> Tab -> Sig -> Spec pvsmaska b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unTab b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsmaska" [(Fr,[Fr,Ir,Kr])] [a1,a2,a3] -- | -- 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: pvsmix :: Spec -> Spec -> Spec pvsmix b1 b2 = Spec $ f <$> unSpec b1 <*> unSpec b2 where f a1 a2 = opcs "pvsmix" [(Fr,[Fr,Fr])] [a1,a2] -- | -- 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: pvsmooth :: Spec -> Sig -> Sig -> Spec pvsmooth b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvsmooth" [(Fr,[Fr,Kr,Kr])] [a1,a2,a3] -- | -- Performs morphing (or interpolation) between two source fsigs. -- -- Performs morphing (or interpolation) between two source fsigs. -- -- > fsig pvsmorph fsig1, fsig2, kampint, kfrqint -- -- csound doc: pvsmorph :: Spec -> Spec -> Sig -> Sig -> Spec pvsmorph b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "pvsmorph" [(Fr,[Fr,Fr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: pvsosc :: Sig -> Sig -> Sig -> D -> Spec pvsosc b1 b2 b3 b4 = Spec $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "pvsosc" [(Fr,[Kr,Kr,Kr,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- 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: pvsout :: Spec -> Sig -> SE () pvsout b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "pvsout" [(Xr,[Fr,Kr])] [a1,a2] -- | -- 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: pvspitch :: Tuple a => Spec -> Sig -> a pvspitch b1 b2 = pureTuple $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = mopcs "pvspitch" ([Kr,Kr],[Fr,Kr]) [a1,a2] -- | -- 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: pvstencil :: Spec -> Sig -> Sig -> D -> Spec pvstencil b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "pvstencil" [(Fr,[Fr,Kr,Kr,Ir])] [a1,a2,a3,a4] -- | -- 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: pvsvoc :: Spec -> Spec -> Sig -> Sig -> Spec pvsvoc b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "pvsvoc" [(Fr,[Fr,Fr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: pvswarp :: Spec -> Sig -> Sig -> Spec pvswarp b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "pvswarp" [(Fr,[Fr,Kr,Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3] -- | -- Resynthesise using a FFT overlap-add. -- -- Resynthesise phase vocoder data (f-signal) using a FFT overlap-add. -- -- > ares pvsynth fsrc, [iinit] -- -- csound doc: pvsynth :: Spec -> Sig pvsynth b1 = Sig $ f <$> unSpec b1 where f a1 = opcs "pvsynth" [(Ar,[Fr,Ir])] [a1] -- | -- 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: resyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig resyn b1 b2 b3 b4 b5 = Sig $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unTab b5 where f a1 a2 a3 a4 a5 = opcs "resyn" [(Ar,[Fr,Kr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: sinsyn :: Spec -> Sig -> Sig -> Tab -> Sig sinsyn b1 b2 b3 b4 = Sig $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unTab b4 where f a1 a2 a3 a4 = opcs "sinsyn" [(Ar,[Fr,Kr,Kr,Ir])] [a1,a2,a3,a4] -- | -- 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: tradsyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig tradsyn b1 b2 b3 b4 b5 = Sig $ f <$> unSpec b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unTab b5 where f a1 a2 a3 a4 a5 = opcs "tradsyn" [(Ar,[Fr,Kr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: trcross :: Spec -> Spec -> Sig -> Sig -> Spec trcross b1 b2 b3 b4 = Spec $ f <$> unSpec b1 <*> unSpec b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "trcross" [(Fr,[Fr,Fr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: trfilter :: Spec -> Sig -> Tab -> Spec trfilter b1 b2 b3 = Spec $ f <$> unSpec b1 <*> unSig b2 <*> unTab b3 where f a1 a2 a3 = opcs "trfilter" [(Fr,[Fr,Kr,Ir])] [a1,a2,a3] -- | -- 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: trhighest :: Tuple a => Spec -> Sig -> a trhighest b1 b2 = pureTuple $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = mopcs "trhighest" ([Fr,Kr,Kr],[Fr,Kr]) [a1,a2] -- | -- 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: trlowest :: Tuple a => Spec -> Sig -> a trlowest b1 b2 = pureTuple $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = mopcs "trlowest" ([Fr,Kr,Kr],[Fr,Kr]) [a1,a2] -- | -- 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: trmix :: Spec -> Spec -> Spec trmix b1 b2 = Spec $ f <$> unSpec b1 <*> unSpec b2 where f a1 a2 = opcs "trmix" [(Fr,[Fr,Fr])] [a1,a2] -- | -- 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: trscale :: Spec -> Sig -> Spec trscale b1 b2 = Spec $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "trscale" [(Fr,[Fr,Kr,Kr])] [a1,a2] -- | -- 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: trshift :: Spec -> Sig -> Spec trshift b1 b2 = Spec $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = opcs "trshift" [(Fr,[Fr,Kr,Kr])] [a1,a2] -- | -- 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: trsplit :: Tuple a => Spec -> Sig -> a trsplit b1 b2 = pureTuple $ f <$> unSpec b1 <*> unSig b2 where f a1 a2 = mopcs "trsplit" ([Fr,Fr],[Fr,Kr,Kr,Kr]) [a1,a2] -- ATS. -- | -- 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: atsAdd :: Sig -> Sig -> D -> Tab -> D -> Sig atsAdd b1 b2 b3 b4 b5 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unD b3 <*> unTab b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "ATSadd" [(Ar,[Kr,Kr,Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- 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: atsAddnz :: Sig -> D -> D -> Sig atsAddnz b1 b2 b3 = Sig $ f <$> unSig b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "ATSaddnz" [(Ar,[Kr,Ir,Ir,Ir,Ir])] [a1,a2,a3] -- | -- 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: atsBufread :: Sig -> Sig -> D -> D -> SE () atsBufread b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "ATSbufread" [(Xr,[Kr,Kr,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- 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: atsCross :: Sig -> Sig -> D -> Tab -> Sig -> Sig -> D -> Sig atsCross b1 b2 b3 b4 b5 b6 b7 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unD b3 <*> unTab b4 <*> unSig b5 <*> unSig b6 <*> unD b7 where f a1 a2 a3 a4 a5 a6 a7 = opcs "ATScross" [(Ar,[Kr,Kr,Ir,Ir,Kr,Kr,Ir,Ir,Ir])] [a1 ,a2 ,a3 ,a4 ,a5 ,a6 ,a7] -- | -- 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: atsInfo :: D -> D -> D atsInfo b1 b2 = D $ f <$> unD b1 <*> unD b2 where f a1 a2 = opcs "ATSinfo" [(Ir,[Ir,Ir])] [a1,a2] -- | -- 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: atsInterpread :: Sig -> Sig atsInterpread b1 = Sig $ f <$> unSig b1 where f a1 = opcs "ATSinterpread" [(Kr,[Kr])] [a1] -- | -- 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: atsPartialtap :: Tuple a => D -> a atsPartialtap b1 = pureTuple $ f <$> unD b1 where f a1 = mopcs "ATSpartialtap" ([Kr,Kr],[Ir]) [a1] -- | -- 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: atsRead :: Tuple a => Sig -> D -> D -> a atsRead b1 b2 b3 = pureTuple $ f <$> unSig b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = mopcs "ATSread" ([Kr,Kr],[Kr,Ir,Ir]) [a1,a2,a3] -- | -- 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: atsReadnz :: Sig -> D -> D -> Sig atsReadnz b1 b2 b3 = Sig $ f <$> unSig b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "ATSreadnz" [(Kr,[Kr,Ir,Ir])] [a1,a2,a3] -- | -- 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: atsSinnoi :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig atsSinnoi b1 b2 b3 b4 b5 b6 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unD b5 <*> unD b6 where f a1 a2 a3 a4 a5 a6 = opcs "ATSsinnoi" [(Ar,[Kr,Kr,Kr,Kr,Ir,Ir,Ir,Ir])] [a1 ,a2 ,a3 ,a4 ,a5 ,a6] -- Loris. -- | -- 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: lorismorph :: D -> D -> D -> Sig -> Sig -> Sig -> SE () lorismorph b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unSig b4 <*> unSig b5 <*> unSig b6 where f a1 a2 a3 a4 a5 a6 = opcs "lorismorph" [(Xr,[Ir,Ir,Ir,Kr,Kr,Kr])] [a1,a2,a3,a4,a5,a6] -- | -- 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: lorisplay :: D -> Sig -> Sig -> Sig -> Sig lorisplay b1 b2 b3 b4 = Sig $ f <$> unD b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "lorisplay" [(Ar,[Ir,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- 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: lorisread :: Sig -> Str -> D -> Sig -> Sig -> Sig -> SE () lorisread b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unStr b2 <*> unD b3 <*> unSig b4 <*> unSig b5 <*> unSig b6 where f a1 a2 a3 a4 a5 a6 = opcs "lorisread" [(Xr,[Kr,Sr,Ir,Kr,Kr,Kr,Ir])] [a1,a2,a3,a4,a5,a6]