{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {- | This module provides a type class that automatically selects a filter for a given parameter type. We choose the dependency this way because there may be different ways to specify the filter parameters but there is only one implementation of the filter itself. -} module Synthesizer.LLVM.Causal.Controlled (C(..)) where import qualified Synthesizer.LLVM.Filter.ComplexFirstOrderPacked as ComplexFiltPack import qualified Synthesizer.LLVM.Filter.ComplexFirstOrder as ComplexFilt import qualified Synthesizer.LLVM.Filter.Allpass as Allpass import qualified Synthesizer.LLVM.Filter.FirstOrder as Filt1 import qualified Synthesizer.LLVM.Filter.SecondOrder as Filt2 import qualified Synthesizer.LLVM.Filter.SecondOrderCascade as Cascade import qualified Synthesizer.LLVM.Filter.SecondOrderPacked as Filt2P import qualified Synthesizer.LLVM.Filter.Moog as Moog import qualified Synthesizer.LLVM.Filter.Universal as UniFilter import qualified Synthesizer.LLVM.Causal.Process as Causal import qualified Synthesizer.LLVM.Frame.Stereo as Stereo import qualified LLVM.Extra.Memory as Memory import qualified LLVM.Extra.ScalarOrVector as SoV import qualified LLVM.Extra.Vector as Vector import qualified LLVM.Extra.Arithmetic as A import qualified LLVM.Core as LLVM import LLVM.Core (Value, IsConst, IsSized, ) import qualified Type.Data.Num.Decimal as TypeNum import Type.Data.Num.Decimal.Number ((:*:), ) {- | A filter parameter type uniquely selects a filter function. However it does not uniquely determine the input and output type, since the same filter can run on mono and stereo signals. -} class (a ~ Input parameter b, b ~ Output parameter a) => C parameter a b where type Input parameter b :: * type Output parameter a :: * process :: (Causal.C process) => process (parameter, a) b {- Instances for the particular filters shall be defined here in order to avoid orphan instances. -} instance (a ~ A.Scalar v, A.PseudoModule v, A.IntegerConstant a, Memory.C a, Memory.C v) => C (Filt1.Parameter a) v (Filt1.Result v) where type Input (Filt1.Parameter a) (Filt1.Result v) = v type Output (Filt1.Parameter a) v = Filt1.Result v process = Filt1.causal instance (a ~ A.Scalar v, A.PseudoModule v, A.RationalConstant a, Memory.C a, Memory.C v) => C (Filt2.Parameter a) v v where type Input (Filt2.Parameter a) v = v type Output (Filt2.Parameter a) v = v process = Filt2.causal instance (Vector.Arithmetic a, SoV.RationalConstant a, Memory.C (Value (Filt2P.State a)) {-, Memory.FirstClass a am, IsSized (Vector TypeNum.D4 a) as, IsSized am ams, LLVM.IsPrimitive am -}) => C (Filt2P.Parameter a) (Value a) (Value a) where type Input (Filt2P.Parameter a) (Value a) = Value a type Output (Filt2P.Parameter a) (Value a) = Value a process = Filt2P.causal instance (a ~ SoV.Scalar v, SoV.PseudoModule v, SoV.IntegerConstant a, Memory.FirstClass a, IsSized a, IsSized (Memory.Stored a), Memory.FirstClass v, IsSized v, IsSized (Memory.Stored v), TypeNum.Natural n, TypeNum.Positive (n :*: LLVM.UnknownSize)) => C (Cascade.ParameterValue n a) (Value v) (Value v) where type Input (Cascade.ParameterValue n a) (Value v) = Value v type Output (Cascade.ParameterValue n a) (Value v) = Value v process = Cascade.causal instance (a ~ A.Scalar v, A.PseudoModule v, A.RationalConstant a, Memory.C a, Memory.C v) => C (Allpass.Parameter a) v v where type Input (Allpass.Parameter a) v = v type Output (Allpass.Parameter a) v = v process = Allpass.causal instance (a ~ A.Scalar v, A.PseudoModule v, A.RationalConstant a, Memory.C a, Memory.C v, TypeNum.Natural n) => C (Allpass.CascadeParameter n a) v v where type Input (Allpass.CascadeParameter n a) v = v type Output (Allpass.CascadeParameter n a) v = v process = Allpass.cascade instance (A.PseudoModule v, A.Scalar v ~ a, A.IntegerConstant a, Memory.C v, TypeNum.Natural n) => C (Moog.Parameter n a) v v where type Input (Moog.Parameter n a) v = v type Output (Moog.Parameter n a) v = v process = Moog.causal instance (a ~ A.Scalar v, A.PseudoModule v, A.RationalConstant a, Memory.C a, Memory.C v) => C (UniFilter.Parameter a) v (UniFilter.Result v) where type Input (UniFilter.Parameter a) (UniFilter.Result v) = v type Output (UniFilter.Parameter a) v = UniFilter.Result v process = UniFilter.causal instance (A.PseudoRing a, A.RationalConstant a, Memory.C a) => C (ComplexFilt.Parameter a) (Stereo.T a) (Stereo.T a) where type Input (ComplexFilt.Parameter a) (Stereo.T a) = Stereo.T a type Output (ComplexFilt.Parameter a) (Stereo.T a) = Stereo.T a process = ComplexFilt.causal instance (Vector.Arithmetic a, IsConst a, Memory.C (Value (Filt2P.State a))) => {- (Memory.FirstClass a am, Vector.Arithmetic a, LLVM.IsPrimitive am, IsSized am ams, IsSized (Vector TypeNum.D4 a) as) => -} C (ComplexFiltPack.Parameter a) (Stereo.T (Value a)) (Stereo.T (Value a)) where type Input (ComplexFiltPack.Parameter a) (Stereo.T (Value a)) = Stereo.T (Value a) type Output (ComplexFiltPack.Parameter a) (Stereo.T (Value a)) = Stereo.T (Value a) process = ComplexFiltPack.causal