module Synthesizer.State.Interpolation (
zeroPad,
constantPad,
cyclicPad,
extrapolationPad,
skip,
single,
delayPad,
) where
import Synthesizer.Interpolation (T, offset, number, func, )
import qualified Synthesizer.State.Signal as Sig
import Data.Maybe (fromMaybe)
import qualified Algebra.RealRing as RealRing
import NumericPrelude.Numeric
import NumericPrelude.Base
zeroPad :: (RealRing.C t) =>
(T t y -> t -> Sig.T y -> a) ->
y -> T t y -> t -> Sig.T y -> a
zeroPad interpolate z ip phase x =
let (phInt, phFrac) = splitFraction phase
in interpolate ip phFrac
(delayPad z (offset ip phInt) (Sig.append x (Sig.repeat z)))
constantPad :: (RealRing.C t) =>
(T t y -> t -> Sig.T y -> a) ->
T t y -> t -> Sig.T y -> a
constantPad interpolate ip phase x =
let (phInt, phFrac) = splitFraction phase
xPad =
do (xFirst,_) <- Sig.viewL x
return (delayPad xFirst (offset ip phInt) (Sig.extendConstant x))
in interpolate ip phFrac
(fromMaybe Sig.empty xPad)
cyclicPad :: (RealRing.C t) =>
(T t y -> t -> Sig.T y -> a) ->
T t y -> t -> Sig.T y -> a
cyclicPad interpolate ip phase x =
let (phInt, phFrac) = splitFraction phase
in interpolate ip phFrac
(Sig.drop (mod (phInt offset ip) (Sig.length x)) (Sig.cycle x))
extrapolationPad :: (RealRing.C t) =>
(T t y -> t -> Sig.T y -> a) ->
T t y -> t -> Sig.T y -> a
extrapolationPad interpolate ip phase =
interpolate ip (phase fromIntegral (offset ip))
skip :: (RealRing.C t) =>
T t y -> (t, Sig.T y) -> (t, Sig.T y)
skip ip (phase0, x0) =
let (n, frac) = splitFraction phase0
(m, x1) = Sig.dropMarginRem (number ip) n x0
in (fromIntegral m + frac, x1)
single :: (RealRing.C t) =>
T t y -> t -> Sig.T y -> y
single ip phase0 x0 =
uncurry (func ip) $ skip ip (phase0, x0)
delayPad :: y -> Int -> Sig.T y -> Sig.T y
delayPad z n =
if n<0
then Sig.drop (negate n)
else Sig.append (Sig.replicate n z)