csound-expression-5.4.3: library to make electronic music
Safe HaskellNone
LanguageHaskell2010

Csound.Air.Filter

Description

Filters

Synopsis

Documentation

Arguemnts are inversed to get most out of curruing. First come parameters and the last one is the signal.

First order filters

lp1 :: Sig -> Sig -> Sig Source #

First order low pass filter (tone in Csound, 6 dB)

lp1 centerFreq asig

hp1 :: Sig -> Sig -> Sig Source #

First order high pass filter (atone in Csound, 6 dB)

hp1 centerFreq asig

Simple filters

lp :: Sig -> Sig -> Sig -> Sig Source #

Low-pass filter.

lp cutoff resonance sig

hp :: Sig -> Sig -> Sig -> Sig Source #

High-pass filter.

hp cutoff resonance sig

bp :: Sig -> Sig -> Sig -> Sig Source #

Band-pass filter.

bp cutoff resonance sig

br :: Sig -> Sig -> Sig -> Sig Source #

Band-reject filter.

br cutoff resonance sig

alp :: Sig -> Sig -> Sig -> Sig Source #

All-pass filter.

alp cutoff resonance sig

bp2 :: Sig -> Sig -> Sig -> Sig Source #

Resonance band pass filter (yet another implementation, it's reson in Csound)

bp2 centerFreq q asig

br2 :: Sig -> Sig -> Sig -> Sig Source #

Resonance band reject filter (yet another implementation, it's areson in Csound)

br2 centerFreq q asig

Butterworth filters

blp :: Sig -> Sig -> Sig Source #

Low-pass filter.

blp cutoff sig

bhp :: Sig -> Sig -> Sig Source #

High-pass filter.

bhp cutoff sig

bbp :: Sig -> Sig -> Sig -> Sig Source #

Band-pass filter.

bbp cutoff bandwidth sig

bbr :: Sig -> Sig -> Sig -> Sig Source #

Band-regect filter.

bbr cutoff bandwidth sig

Filter order

type ResonFilter = Sig -> Sig -> Sig -> Sig Source #

Resonant filter.

f centerFreq q asig

type FlatFilter = Sig -> Sig -> Sig Source #

Filter without a resonance.

f centerFreq q asig

filt :: Int -> ResonFilter -> ResonFilter Source #

Applies a filter n-times. The n is given in the first rgument.

flatFilt :: Int -> FlatFilter -> FlatFilter Source #

Applies a flat filter (without resonance) n-times. The n is given in the first rgument.

toReson :: FlatFilter -> ResonFilter Source #

Makes fake resonant filter from flat filter. The resulting filter just ignores the resonance.

Specific filters

Moog filters

mlp :: Sig -> Sig -> Sig -> Sig Source #

Moog's low-pass filter.

mlp centerFrequency qResonance signal

mlp2 :: Sig -> Sig -> Sig -> Sig Source #

Another implementation of moog low pass filter (it's moogladder in Csound). The arguments have are just like in the mlp filter.

mlp2 centerFreq q asig

mlp3 :: Sig -> Sig -> Sig -> Sig Source #

Mooglowpass filter with 18 dB.

mlp3 centerFreq q asig

lp18 :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Low pass filter 18 dB with built in distortion module.

lp18 distortion centerFreq resonance asig
  • distortion's range is 0 to 1
  • resonance's range is 0 to 1

ladder :: Sig -> Sig -> Sig -> Sig Source #

Moog ladder filter

ladder centerFreq q asig

Formant filters

formant :: ResonFilter -> [(Sig, Sig)] -> Sig -> Sig Source #

Formant filter.

formant bandPassFilter formants asig

It expects a band pass filter, a list of formants and processed signal. The signal is processed with each filter the result is a sum of all proceessed signals. Formant filters are used to mimic the vocalization of the sound.

singA :: Sig -> Sig Source #

Formant filter that sings an A.

singO :: Sig -> Sig Source #

Formant filter that sings an O.

singE :: Sig -> Sig Source #

Formant filter that sings an E.

singU :: Sig -> Sig Source #

Formant filter that sings an U.

singO2 :: Sig -> Sig Source #

Formant filter that sings an O.

Making the smooth lines

smooth :: Sig -> Sig -> Sig Source #

Produces smooth transitions between values in the signals. The first value defines a duration in seconds for a transition from one value to another in piecewise constant signals.

smooth transTime asig

slide :: Sig -> Sig -> Sig Source #

Makes slides between values in the signals. The first value defines a duration in seconds for a transition from one value to another in piecewise constant signals.

Analog filters

Requires Csound 6.07 or higher

alp1 :: Sig -> Sig -> Sig -> Sig Source #

Analog-like low-pass filter

alpf1 centerFrequency resonance asig

alp2 :: Sig -> Sig -> Sig -> Sig Source #

Analog-like low-pass filter

alpf2 centerFrequency resonance asig

alp3 :: Sig -> Sig -> Sig -> Sig Source #

Analog-like low-pass filter

alpf3 centerFrequency resonanceance asig

alp4 :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig) Source #

Analog-like low-pass filter

alpf4 centerFrequency resonance asig

Analog outputs

  • asig1 -- 6dB/oct low-pass response output.
  • asig2 -- 12dB/oct low-pass response output.
  • asig3 -- 18dB/oct low-pass response output..
  • asig4 -- 24dB/oct low-pass response output.

ahp :: Sig -> Sig -> Sig Source #

Analog-like high-pass filter

ahp centerFrequency asig

Zero delay filters

One pole filters

zdf1 :: Sig -> Sig -> (Sig, Sig) Source #

Zero-delay feedback implementation of 1 pole filter.

ouputs low-pass and high-pass signals.

zdf1 centerFreq asig = (alp, ahp)

zlp1 :: Sig -> Sig -> Sig Source #

Zero-delay feedback implementation of 1 pole low-pass filter.

zlp1 centerFreq asig

zhp1 :: Sig -> Sig -> Sig Source #

Zero-delay feedback implementation of 1 pole high-pass filter.

zhp1 centerFreq asig

zap1 :: Sig -> Sig -> Sig Source #

Zero-delay feedback implementation of 1 pole allpass filter.

zap1 centerFreq asig

Two pole filters

zdf2 :: Sig -> Sig -> Sig -> (Sig, Sig, Sig) Source #

zero delay feedback 2 pole filter

zdf2 centerFreq q asig = (alp, abp, ahp)

zlp :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole Low pass filter. Q is unipolar [0, 1]

zlp centerFreq q asig

zhp :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole High pass filter. Q is unipolar [0, 1]

zhp centerFreq q asig

zbp :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole Band pass. Q is unipolar [0, 1]

zbp centerFreq q asig

zubp :: Sig -> Sig -> Sig -> Sig Source #

Unity-gain bandpass (zero delay feedback 2 pole). Q is unipolar [0, 1]

zubp centerFreq q asig

zbr :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole Notch (band reject). Q is unipolar [0, 1]

zbr centerFreq q asig

zap :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole Allpass filter. Q is unipolar [0, 1]

zap centerFreq q asig

zpeak :: Sig -> Sig -> Sig -> Sig Source #

zero delay feedback 2 pole Peak filter. Q is unipolar [0, 1]

zpeak centerFreq q asig

Ladder filter

zladder :: Sig -> Sig -> Sig -> Sig Source #

Zero-delay feedback implementation of 4 pole ladder filter. Q is unipolar [0, 1]

zladder centerFreq q asig

Four poles filters

Eq-filters

Classic analog-like filters

low pass

lpCheb1 :: Sig -> Sig -> Sig Source #

Chebyshev type I low pass filter (with 2 poles).

lpCheb1 centerFreq asig

lpCheb1' :: D -> Sig -> Sig -> Sig Source #

Chebyshev type I low pass filter (with given number of poles, first argument).

lpCheb1' npols centerFreq asig

lpCheb2 :: Sig -> Sig -> Sig Source #

Chebyshev type II low pass filter (with 2 poles).

lpCheb2 centerFreq asig

lpCheb2' :: D -> Sig -> Sig -> Sig Source #

Chebyshev type II low pass filter (with given number of poles, first argument).

lpCheb2' npols centerFreq asig

clp :: Sig -> Sig -> Sig Source #

Butterworth lowpass filter based on clfilt opcode (with 2 poles).

clp centerFreq asig

clp' :: D -> Sig -> Sig -> Sig Source #

Butterworth lowpass filter based on clfilt opcode (with given number of poles, first argument).

clp' npols centerFreq asig

band pass

bpCheb1 :: Sig -> Sig -> Sig -> Sig Source #

bpCheb1' :: D -> Sig -> Sig -> Sig -> Sig Source #

bpCheb2 :: Sig -> Sig -> Sig -> Sig Source #

bpCheb2' :: D -> Sig -> Sig -> Sig -> Sig Source #

cbp :: Sig -> Sig -> Sig -> Sig Source #

cbp' :: D -> Sig -> Sig -> Sig -> Sig Source #

high pass

hpCheb1 :: Sig -> Sig -> Sig Source #

Chebyshev type I high pass filter (with 2 poles).

hpCheb1 centerFreq asig

hpCheb1' :: D -> Sig -> Sig -> Sig Source #

Chebyshev type I high pass filter (with given number of poles, first argument).

hpCheb1' npols centerFreq asig

hpCheb2 :: Sig -> Sig -> Sig Source #

Chebyshev type II high pass filter (with 2 poles).

hpCheb2 centerFreq asig

hpCheb2' :: D -> Sig -> Sig -> Sig Source #

Chebyshev type II high pass filter (with given number of poles, first argument).

hpCheb2' npols centerFreq asig

chp :: Sig -> Sig -> Sig Source #

Butterworth high pass filter based on clfilt opcode (with 2 poles).

chp centerFreq asig

chp' :: D -> Sig -> Sig -> Sig Source #

Butterworth high pass filter based on clfilt opcode (with given number of poles, first argument).

chp' npols centerFreq asig

cheb1 :: Sig -> Sig -> Sig -> Sig Source #

cheb2 :: Sig -> Sig -> Sig -> Sig Source #

vcf :: Sig -> Sig -> Sig -> Sig Source #

cheb1' :: D -> Sig -> Sig -> Sig -> Sig Source #

cheb2' :: D -> Sig -> Sig -> Sig -> Sig Source #

vcf' :: D -> Sig -> Sig -> Sig -> Sig Source #

Named resonant low pass filters

plastic :: Sig -> Sig -> Sig -> Sig Source #

plastic sound

plastic centerFreq q asig

wobble :: Sig -> Sig -> Sig -> Sig Source #

wobble sound

wobble centerFreq q asig

trumpy :: Sig -> Sig -> Sig -> Sig Source #

trumpy sound

trumpy centerFreq q asig

harsh :: Sig -> Sig -> Sig -> Sig Source #

harsh sound

harsh centerFreq q asig

TB303 filter

tbf :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Fixed version of tbfcv filter the first argument is distortion (range [0, 1])

diode :: D -> Sig -> Sig -> Sig -> Sig Source #

Zero-delay feedback implementation of 4 pole diode ladder filter (24 dB/oct) . This filter design was originally used in the EMS VCS3 and was the resonant filter in the Roland TB-303.

  • Q is unipolar [0, 1]
  • saturation - amount to use for non-linear processing. Values > 1 increase the steepness of the NLP curve.
diode saturation centerFreq q asig

fdiode :: D -> Sig -> Sig -> Sig -> Sig Source #

Faster diode, but lesser quality

fdiode saturation centerFreq q asig

linDiode :: Sig -> Sig -> Sig -> Sig Source #

Linear diode, no saturation involved

linDiode centerFreq q asig

linKorg_lp :: Sig -> Sig -> Sig -> Sig Source #

Linear Korg35 resonant low-pass filter

linKorg_lp centerFreq q asig

linKorg_hp :: Sig -> Sig -> Sig -> Sig Source #

Linear Korg35 resonant high-pass filter

linKorg_hp centerFreq q asig

korg_lp :: D -> Sig -> Sig -> Sig -> Sig Source #

Korg35 resonant low-pass filter. Q is unipolar [0, 1]

korg_lp saturation centerFreq q asig

korg_hp :: D -> Sig -> Sig -> Sig -> Sig Source #

Korg35 resonant high-pass filter. Q is unipolar [0, 1]

korg_hp saturation centerFreq q asig

korg_bp :: D -> Sig -> Sig -> Sig -> Sig Source #

Korg35 resonant band-pass filter. Q is unipolar [0, 1]

korg_bp saturation centerFreq q asig

klp :: D -> Sig -> Sig -> Sig -> Sig Source #

Alias for korg_lp

khp :: D -> Sig -> Sig -> Sig -> Sig Source #

Alias for korg_hp

kbp :: D -> Sig -> Sig -> Sig -> Sig Source #

Alias for korg_bp

Statevariable filters

slp :: Sig -> Sig -> Sig -> Sig Source #

State variable low-pass filter

shp :: Sig -> Sig -> Sig -> Sig Source #

State variable high-pass filter

sbp :: Sig -> Sig -> Sig -> Sig Source #

State variable band-pass filter

sbr :: Sig -> Sig -> Sig -> Sig Source #

State variable band-reject filter

Multimode filters

multiStatevar :: (Sig, Sig, Sig) -> Sig -> Sig -> Sig -> Sig Source #

multiSvfilter :: (Sig, Sig, Sig) -> Sig -> Sig -> Sig -> Sig Source #