{-# OPTIONS -fno-implicit-prelude #-} {- | ToDo: use AffineSpace instead of Module for the particular interpolation types, since affine combinations assert reconstruction of constant functions. They are more natural for interpolation of internal control parameters. However, how can cubic interpolation expressed by affine combinations without divisions? -} module Synthesizer.Causal.Interpolation ( Interpolation.T, Interpolation.toGeneric, relative, relativeZeroPad, relativeConstantPad, relativeCyclicPad, relativeExtrapolationPad, relativeZeroPadConstant, relativeZeroPadLinear, relativeZeroPadCubic, ) where import qualified Synthesizer.State.Interpolation as Interpolation import qualified Synthesizer.Causal.Process as Causal import qualified Synthesizer.State.Signal as Sig import qualified Algebra.Module as Module import qualified Algebra.RealField as RealField import qualified Algebra.Additive as Additive import Algebra.Additive(zero) import PreludeBase import NumericPrelude {-* Interpolation at multiple nodes with various padding methods -} {- | All values of frequency control must be non-negative. -} {-# INLINE relative #-} relative :: (RealField.C t) => Interpolation.T t y -> t -> Sig.T y -> Causal.T t y relative ip phase0 x0 = Causal.crochetL (\freq pos -> let (phase,x) = Interpolation.skip ip pos in Just (Interpolation.func ip phase x, (phase+freq,x))) (phase0,x0) {-# INLINE relativeZeroPad #-} relativeZeroPad :: (RealField.C t) => y -> Interpolation.T t y -> t -> Sig.T y -> Causal.T t y relativeZeroPad z ip phase x = Interpolation.zeroPad relative z ip phase x {-# INLINE relativeConstantPad #-} relativeConstantPad :: (RealField.C t) => Interpolation.T t y -> t -> Sig.T y -> Causal.T t y relativeConstantPad ip phase x = Interpolation.constantPad relative ip phase x {-# INLINE relativeCyclicPad #-} relativeCyclicPad :: (RealField.C t) => Interpolation.T t y -> t -> Sig.T y -> Causal.T t y relativeCyclicPad ip phase x = Interpolation.cyclicPad relative ip phase x {- | The extrapolation may miss some of the first and some of the last points -} {-# INLINE relativeExtrapolationPad #-} relativeExtrapolationPad :: (RealField.C t) => Interpolation.T t y -> t -> Sig.T y -> Causal.T t y relativeExtrapolationPad ip phase x = Interpolation.extrapolationPad relative ip phase x {- This example shows pikes, although there shouldn't be any: plotList (take 100 $ interpolate (Zero (0::Double)) ipCubic (-0.9::Double) (repeat 0.03) [1,0,1,0.8]) -} {-* All-in-one interpolation functions -} {-# INLINE relativeZeroPadConstant #-} relativeZeroPadConstant :: (RealField.C t, Additive.C y) => t -> Sig.T y -> Causal.T t y relativeZeroPadConstant = relativeZeroPad zero Interpolation.constant {-# INLINE relativeZeroPadLinear #-} relativeZeroPadLinear :: (RealField.C t, Module.C t y) => t -> Sig.T y -> Causal.T t y relativeZeroPadLinear = relativeZeroPad zero Interpolation.linear {-# INLINE relativeZeroPadCubic #-} relativeZeroPadCubic :: (RealField.C t, Module.C t y) => t -> Sig.T y -> Causal.T t y relativeZeroPadCubic = relativeZeroPad zero Interpolation.cubic