{- | Copyright : (c) Henning Thielemann 2008 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes -} module Synthesizer.Dimensional.Rate.Analysis ( centroid, length, centroidProc, lengthProc, ) where import qualified Synthesizer.Dimensional.Straight.Signal as SigS import qualified Synthesizer.Dimensional.RateWrapper as SigP import qualified Synthesizer.State.Analysis as Ana import qualified Synthesizer.State.Signal as Sig import qualified Synthesizer.Dimensional.Process as Proc import qualified Number.DimensionTerm as DN import qualified Algebra.DimensionTerm as Dim import Number.DimensionTerm ((*&)) import qualified Algebra.Field as Field -- import qualified Algebra.Real as Real -- import qualified Algebra.Ring as Ring import PreludeBase ((.), ($), ) import NumericPrelude import Prelude () {-# INLINE centroid #-} centroid :: (Field.C q, Dim.C u) => SigP.T u q (SigS.T Sig.T) q -> DN.T u q centroid = makePhysicalLength Ana.centroid {-# INLINE length #-} length :: (Field.C t, Dim.C u) => SigP.T u t (SigS.T Sig.T) yv -> DN.T u t length = makePhysicalLength (fromIntegral . Sig.length) {-# INLINE makePhysicalLength #-} makePhysicalLength :: (Field.C t, Dim.C u) => (Sig.T y -> t) -> SigP.T u t (SigS.T Sig.T) y -> DN.T u t makePhysicalLength f x = f (SigS.samples (SigP.signal x)) *& DN.unrecip (SigP.sampleRate x) {-# DEPRECATED #-} {-# INLINE centroidProc #-} centroidProc :: (Field.C y, Dim.C u) => Proc.T s u y (SigS.R s y -> DN.T u y) centroidProc = makePhysicalLengthProc Ana.centroid {-# DEPRECATED #-} {-# INLINE lengthProc #-} lengthProc :: (Field.C y, Dim.C u) => Proc.T s u y (SigS.R s y -> DN.T u y) lengthProc = makePhysicalLengthProc (fromIntegral . Sig.length) {-# INLINE makePhysicalLengthProc #-} makePhysicalLengthProc :: (Field.C t, Dim.C u) => (Sig.T y -> t) -> Proc.T s u t ( SigS.R s y -> DN.T u t) makePhysicalLengthProc f = Proc.withParam $ Proc.toTimeDimension . f . SigS.toSamples