synthesizer-0.2.0.1: Audio signal processing coded in HaskellSource codeContentsIndex
Synthesizer.Dimensional.Causal.Filter
Portabilityrequires multi-parameter type classes
Stabilityprovisional
Maintainersynthesizer@henning-thielemann.de
Contents
Non-recursive
Amplification
Filter operators from calculus
Recursive
Without resonance
With resonance
Allpass
Filter operators from calculus
Description
Synopsis
amplify :: C y amp => y -> T s u t (T s amp amp yv yv)
amplifyDimension :: (C y, C u, C v0, C v1) => T v0 y -> T s u t (T s (T v1 y) (T (Mul v0 v1) y) yv yv)
negate :: C yv => T s u t (T s amp amp yv yv)
envelope :: C y => T s u t (T s (Flat, amp) amp (y, y) y)
envelopeVector :: C y yv => T s u t (T s (Flat, amp) amp (y, yv) yv)
envelopeVectorDimension :: (C y0 yv, C y, C u, C v0, C v1) => T s u t (T s (T v0 y, T v1 y) (T (Mul v0 v1) y) (y0, yv) yv)
differentiate :: (C yv, C q, C u, C v) => T s u q (T s (T v q) (T (DimensionGradient u v) q) yv yv)
type ResonantFilter s u q ic amp yv0 yv1 = T s u q (T (Converter s (Scalar q, T (Recip u) q) (q, q) ic) (T s (amp, Flat) amp (yv0, RateDep s ic) yv1))
type FrequencyFilter s u q ic amp yv0 yv1 = T s u q (T (Converter s (T (Recip u) q) q ic) (T s (amp, Flat) amp (yv0, RateDep s ic) yv1))
firstOrderLowpass :: (C q, C q yv, C u) => FrequencyFilter s u q (Parameter q) amp yv yv
firstOrderHighpass :: (C q, C q yv, C u) => FrequencyFilter s u q (Parameter q) amp yv yv
butterworthLowpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (Parameter a) amp yv yv
butterworthHighpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (Parameter a) amp yv yv
chebyshevALowpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterA a) amp yv yv
chebyshevAHighpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterA a) amp yv yv
chebyshevBLowpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterB a) amp yv yv
chebyshevBHighpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterB a) amp yv yv
butterworthLowpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
butterworthHighpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
chebyshevALowpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
chebyshevAHighpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
chebyshevBLowpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
chebyshevBHighpassPole :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Pole q) amp yv yv
universal :: (C q, C q yv, C u) => ResonantFilter s u q (Parameter q) amp yv (Result yv)
highpassFromUniversal :: T s amp amp (Result yv) yv
bandpassFromUniversal :: T s amp amp (Result yv) yv
lowpassFromUniversal :: T s amp amp (Result yv) yv
bandlimitFromUniversal :: T s amp amp (Result yv) yv
moogLowpass :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Parameter q) amp yv yv
allpassCascade :: (C q, C q yv, C u) => Int -> q -> FrequencyFilter s u q (Parameter q) amp yv yv
allpassPhaser :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (q, Parameter q) amp yv yv
allpassFlangerPhase :: C a => a
integrate :: (C yv, C q, C u, C v) => T s u q (T s (T v q) (T (Mul u v) q) yv yv)
Non-recursive
Amplification
amplify :: C y amp => y -> T s u t (T s amp amp yv yv)Source
The amplification factor must be positive.
amplifyDimension :: (C y, C u, C v0, C v1) => T v0 y -> T s u t (T s (T v1 y) (T (Mul v0 v1) y) yv yv)Source
negate :: C yv => T s u t (T s amp amp yv yv)Source
envelope :: C y => T s u t (T s (Flat, amp) amp (y, y) y)Source
envelopeVector :: C y yv => T s u t (T s (Flat, amp) amp (y, yv) yv)Source
envelopeVectorDimension :: (C y0 yv, C y, C u, C v0, C v1) => T s u t (T s (T v0 y, T v1 y) (T (Mul v0 v1) y) (y0, yv) yv)Source
Filter operators from calculus
differentiate :: (C yv, C q, C u, C v) => T s u q (T s (T v q) (T (DimensionGradient u v) q) yv yv)Source
Recursive
type ResonantFilter s u q ic amp yv0 yv1 = T s u q (T (Converter s (Scalar q, T (Recip u) q) (q, q) ic) (T s (amp, Flat) amp (yv0, RateDep s ic) yv1))Source
type FrequencyFilter s u q ic amp yv0 yv1 = T s u q (T (Converter s (T (Recip u) q) q ic) (T s (amp, Flat) amp (yv0, RateDep s ic) yv1))Source
Without resonance
firstOrderLowpass :: (C q, C q yv, C u) => FrequencyFilter s u q (Parameter q) amp yv yvSource
firstOrderHighpass :: (C q, C q yv, C u) => FrequencyFilter s u q (Parameter q) amp yv yvSource
butterworthLowpassSource
:: (C a, C a yv, Storable a, Storable yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u a (Parameter a) amp yv yv
butterworthHighpassSource
:: (C a, C a yv, Storable a, Storable yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u a (Parameter a) amp yv yv
chebyshevALowpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterA a) amp yv yvSource
chebyshevAHighpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterA a) amp yv yvSource
chebyshevBLowpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterB a) amp yv yvSource
chebyshevBHighpass :: (C a, C a yv, Storable a, Storable yv, C u) => Int -> ResonantFilter s u a (ParameterB a) amp yv yvSource
butterworthLowpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
butterworthHighpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
chebyshevALowpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
chebyshevAHighpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
chebyshevBLowpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
chebyshevBHighpassPoleSource
:: (C q, C q yv, C u)
=> IntOrder of the filter, must be even, the higher the order, the sharper is the separation of frequencies.
-> ResonantFilter s u q (Pole q) amp yv yv
With resonance
universal :: (C q, C q yv, C u) => ResonantFilter s u q (Parameter q) amp yv (Result yv)Source
highpassFromUniversal :: T s amp amp (Result yv) yvSource
bandpassFromUniversal :: T s amp amp (Result yv) yvSource
lowpassFromUniversal :: T s amp amp (Result yv) yvSource
bandlimitFromUniversal :: T s amp amp (Result yv) yvSource
moogLowpass :: (C q, C q yv, C u) => Int -> ResonantFilter s u q (Parameter q) amp yv yvSource
Allpass
allpassCascadeSource
:: (C q, C q yv, C u)
=> Intorder, number of filters in the cascade
-> qthe phase shift to be achieved for the given frequency
-> FrequencyFilter s u q (Parameter q) amp yv yv
the lowest comb frequency is used as the filter frequency
allpassPhaserSource
:: (C q, C q yv, C u)
=> Intorder, number of filters in the cascade
-> ResonantFilter s u q (q, Parameter q) amp yv yv
We use the mixing ratio as resonance parameter. Mixing ratio r means: Amplify input by r and delayed signal by 1-r. Maximum effect is achieved for r=0.5.
allpassFlangerPhase :: C a => aSource
Filter operators from calculus
integrate :: (C yv, C q, C u, C v) => T s u q (T s (T v q) (T (Mul u v) q) yv yv)Source
Produced by Haddock version 2.4.2