{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} module Synthesizer.Filter.Basic where import qualified Algebra.Transcendental as Trans import qualified Algebra.Module as Module import qualified Algebra.RealField as RealField import qualified Number.Complex as Complex import NumericPrelude import PreludeBase {- todo: - support of data before time 0 - the problem is that all past data has to be kept, the garbage collector can't flush it :-( - this means we will also need functions for plain lists, in this case we can't provide initial conditions to recursive filters - the question of initial conditions is especially problematic since for Graphs we have no explicit feed back where initial conditions can be plugged in - thus for two-way signal we must request the user to insert initial conditions in every loop of a Graph using the Past constructor - all of the following filter primitives in static and modulated form: - mask - integer delay - fractional delay - shall the fractional delay constructor store the interpolation type? (this discussion is similar to the one concerning initial conditions for recursive filters) - yes, because each delay may use a different interpolation type, if no fractional delay is used, no interpolation type needs to be specified - no, because the interpolation is only of interest for filter application not for the transfer function - Is there a way to avoid the multi-parameter type class? - Can we provide a class for lists (OneWay and TwoWay) that help implementing filters and filter networks? - The 'transferFunction' obviously does not depend on the signal list type. - 'transferFunction' should not be restricted to complex numbers. - For arguments of type 'Ratio (Polynomial Rational)' you could compute the transfer function in terms of a rational function. -} screw :: Trans.C a => a -> [Complex.T a] screw w = iterate (Complex.cis w *) 1 class Filter list filter | filter -> list where {-| Apply a filter to a signal. -} apply :: (RealField.C t, Trans.C t, Module.C a v, Module.C a (list v)) => filter t a v -> list v -> list v {-| Compute the complex amplification factor that is applied to the given frequency. -} transferFunction :: (Trans.C t, Module.C a t) => filter t a v -> t -> Complex.T t