{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RebindableSyntax #-} module SignalProcessingLLVM where import qualified Synthesizer.LLVM.CausalParameterized.Process as CausalP import qualified Synthesizer.LLVM.Parameter as Param import qualified LLVM.Extra.Class as Class import qualified LLVM.Extra.Memory as Memory import LLVM.Core (Value, ) import Foreign.Storable (Storable, ) import qualified Control.Category as Cat import Control.Arrow (arr, (<<<), (^<<), (&&&), ) import Control.Applicative (pure, ) import Data.Tuple.HT (fst3, snd3, thd3, ) import NumericPrelude.Numeric import NumericPrelude.Base zerothMoment :: CausalP.T p (Value Float) (Value Float) zerothMoment = CausalP.delay1Zero firstMoment :: CausalP.T p (Value Float) (Value Float) firstMoment = ((arr thd3 - arr fst3) / 2) <<< lag2 secondMoment :: CausalP.T p (Value Float) (Value Float) secondMoment = (arr thd3 - 2 * arr snd3 + arr fst3) <<< lag2 lag2 :: CausalP.T p (Value Float) (Value Float, Value Float, Value Float) lag2 = lag2Init $ pure (zero :: Float) lag2Init :: (Storable a, Class.MakeValueTuple a, Memory.C al, Class.ValueTuple a ~ al) => Param.T p a -> CausalP.T p al (al,al,al) lag2Init x = (\((x0,x1),x2) -> (x0,x1,x2)) ^<< (CausalP.delay1 x &&& Cat.id <<< CausalP.delay1 x) &&& Cat.id