csound-expression-0.1.0: Csound combinator library

CsoundExpr.Opcodes.Sigmod.Speciali

Description

Specialized Filters

Synopsis

Documentation

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

  • opcode : dcblock
  • syntax :
   ares dcblock ain [, igain]
  • description :

Implements the DC blocking filter

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

  • opcode : dcblock2
  • syntax :
   ares dcblock2 ain [, iorder] [, iskip]
  • description :

Implements a DC blocking filter with improved DC attenuation.

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

  • opcode : pareq
  • syntax :
   ares pareq asig, kc, kv, kq [, imode] [, iskip]
  • description :

Implementation of Zoelzer's parametric equalizer filters, with some modifications by the author.

rbjeq :: (K k0, K k1, K k2, K k3) => [Irate] -> Arate -> k0 -> k1 -> k2 -> k3 -> ArateSource

  • opcode : rbjeq
  • syntax :
   ar rbjeq asig, kfco, klvl, kQ, kS[, imode]
  • description :

Parametric equalizer and filter opcode with 7 filter types, based on algorithm by Robert Bristow-Johnson.

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

  • opcode : eqfil
  • syntax :
   asig eqfil ain, kcf, kbw, kgain[, istor]
  • description :

The opcode eqfil is a 2nd order tunable equalisation filter based on Regalia and Mitra design (Tunable Digital Frequency Response Equalization Filters, IEEE Trans. on Ac., Sp. and Sig Proc., 35 (1), 1987). It provides a peak/notch filter for building parametric/graphic equalisers.

nlfilt :: (K k0, K k1, K k2, K k3, K k4) => Arate -> k0 -> k1 -> k2 -> k3 -> k4 -> ArateSource

  • opcode : nlfilt
  • syntax :
   ares nlfilt ain, ka, kb, kd, kC, kL
  • description :

Implements the filter:

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

  • opcode : filter2
  • syntax :
   ares filter2 asig, iM, iN, ib0, ib1,..., ibM, ia1, ia2,..., iaN
   kres filter2 ksig, iM, iN, ib0, ib1,..., ibM, ia1, ia2,..., iaN
  • description :

General purpose custom filter with time-varying pole control. The filter coefficients implement the following difference equation:

filter2K :: K k0 => k0 -> Irate -> Irate -> [Irate] -> [Irate] -> KrateSource

  • opcode : filter2
  • syntax :
   ares filter2 asig, iM, iN, ib0, ib1,..., ibM, ia1, ia2,..., iaN
   kres filter2 ksig, iM, iN, ib0, ib1,..., ibM, ia1, ia2,..., iaN
  • description :

General purpose custom filter with time-varying pole control. The filter coefficients implement the following difference equation:

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

  • opcode : fofilter
  • syntax :
   asig fofilter ain, kcf, kris, kdec[, istor]
  • description :

Fofilter generates a stream of overlapping sinewave grains, when fed with a pulse train. Each grain is the impulse response of a combination of two BP filters. The grains are defined by their attack time (determining the skirtwidth of the formant region at -60dB) and decay time (-6dB bandwidth). Overlapping will occur when 1/freq < decay, but, unlike FOF, there is no upper limit on the number of overlaps. The original idea for this opcode came from J McCartney's formlet class in SuperCollider, but this is possibly implemented differently(?).

hilbert :: Arate -> MultiOutSource

  • opcode : hilbert
  • syntax :
   ar1, ar2 hilbert asig
  • description :

An IIR implementation of a Hilbert transformer.

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

  • opcode : zfilter2
  • syntax :
   ares zfilter2 asig, kdamp, kfreq, iM, iN, ib0, ib1,..., ibM, 
       ia1,ia2,..., iaN
  • description :

General purpose custom filter with time-varying pole control. The filter coefficients implement the following difference equation: