csound-expression-0.0: Csound combinator library

CsoundExpr.Opcodes.Sigmod.Reverbtn

Description

Reverberation

Synopsis

Documentation

alpass :: K k0 => [Irate] -> Arate -> k0 -> Irate -> ArateSource

  • opcode : alpass
  • syntax :
   ares alpass asig, krvt, ilpt [, iskip] [, insmps]
  • description :

Reverberates an input signal with a flat frequency response.

babo :: (K k0, K k1, K k2) => [Irate] -> Arate -> k0 -> k1 -> k2 -> Irate -> Irate -> Irate -> MultiOutSource

  • opcode : babo
  • syntax :
   a1, a2 babo asig, ksrcx, ksrcy, ksrcz, irx, iry, irz [, idiff] [, ifno]
  • description :

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

comb :: K k0 => [Irate] -> Arate -> k0 -> Irate -> ArateSource

  • opcode : comb
  • syntax :
   ares comb asig, krvt, ilpt [, iskip] [, insmps]
  • description :

Reverberates an input signal with a colored frequency response.

freeverb :: (K k0, K k1) => [Irate] -> Arate -> Arate -> k0 -> k1 -> MultiOutSource

  • opcode : freeverb
  • syntax :
   aoutL, aoutR freeverb ainL, ainR, kRoomSize, kHFDamp[, iSRate[, iSkip]]
  • description :

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

nestedap :: [Irate] -> Arate -> Irate -> Irate -> Irate -> Irate -> ArateSource

  • opcode : nestedap
  • syntax :
   ares nestedap asig, imode, imaxdel, idel1, igain1 [, idel2] [, igain2] 
       [, idel3] [, igain3] [, istor]
  • description :

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

nreverb :: (K k0, K k1) => [Irate] -> Arate -> k0 -> k1 -> ArateSource

  • opcode : nreverb
  • syntax :
   ares nreverb asig, ktime, khdif [, iskip] [,inumCombs] [, ifnCombs] 
       [, inumAlpas] [, ifnAlpas]
  • description :

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

reverb2 :: (K k0, K k1) => [Irate] -> Arate -> k0 -> k1 -> ArateSource

  • opcode : reverb2
  • syntax :
   ares reverb2 asig, ktime, khdif [, iskip] [,inumCombs] 
       [, ifnCombs] [, inumAlpas] [, ifnAlpas]
  • description :

Same as the nreverb opcode.

reverb :: K k0 => [Irate] -> Arate -> k0 -> ArateSource

  • opcode : reverb
  • syntax :
   ares reverb asig, krvt [, iskip]
  • description :

Reverberates an input signal with a natural room frequency response.

reverbsc :: (K k0, K k1) => [Irate] -> Arate -> Arate -> k0 -> k1 -> MultiOutSource

  • opcode : reverbsc
  • syntax :
   aoutL, aoutR reverbsc ainL, ainR, kfblvl, kfco[, israte[, ipitchm[, iskip]]]
  • description :

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

valpass :: (K k0, X x0) => [Irate] -> Arate -> k0 -> x0 -> Irate -> ArateSource

  • opcode : valpass
  • syntax :
   ares valpass asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
  • description :

Variably reverberates an input signal with a flat frequency response.

vcomb :: (K k0, X x0) => [Irate] -> Arate -> k0 -> x0 -> Irate -> ArateSource

  • opcode : vcomb
  • syntax :
   ares vcomb asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
  • description :

Variably reverberates an input signal with a colored frequency response.