module DSP.Filter.Analog.Prototype where
import Data.Complex (Complex((:+)), realPart)
import Polynomial.Basic (roots2poly)
butterworth :: Int
-> ([Double],[Double])
butterworth n = (num, den)
where poles = [ (-u k) :+ (w k) | k <- [0..(n-1)] ]
u k = sin (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
w k = cos (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
num = [ 1 ]
den = map realPart $ roots2poly $ poles
chebyshev1 :: Double
-> Int
-> ([Double],[Double])
chebyshev1 eps n = (num, den)
where poles = [ (-u k) :+ (w k) | k <- [0..(n-1)] ]
u k = sinh v0 * sin (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
w k = cosh v0 * cos (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
num = [ gain ]
den = map realPart $ roots2poly $ poles
v0 = asinh (1/eps) / fromIntegral n
gain =
if even n
then abs $ head den / sqrt (1 + eps^(2::Int))
else abs $ head den
chebyshev2 :: Double
-> Int
-> ([Double],[Double])
chebyshev2 eps n = (num, den)
where zeros = [ 0 :+ 1 / wz k | k <- [0..(n-1)], 2*k+1 /= n ]
poles = [ 1 / ((-u k) :+ (w k)) | k <- [0..(n-1)] ]
wz k = cos (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
u k = sinh v0 * sin (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
w k = cosh v0 * cos (fromIntegral (2*k+1) * pi / fromIntegral (2*n))
num = map (*gain) $ map realPart $ roots2poly $ zeros
den = map realPart $ roots2poly $ poles
v0 = asinh (1/eps) / fromIntegral n
gain = abs $ realPart $ product poles / product zeros