module Synthesizer.Interpolation.Custom (
T,
constant,
linear,
cubic,
piecewise,
piecewiseConstant,
piecewiseLinear,
piecewiseCubic,
function,
) where
import qualified Synthesizer.State.Signal as Sig
import qualified Synthesizer.Plain.Control as Ctrl
import qualified Synthesizer.Interpolation.Class as Interpol
import Synthesizer.Interpolation (
T, cons, getNode, fromPrefixReader,
constant,
)
import qualified Algebra.Field as Field
import Synthesizer.Interpolation.Class ((+.*), )
import qualified Control.Applicative.HT as App
import NumericPrelude.Numeric
import NumericPrelude.Base
linear :: (Interpol.C t y) => T t y
linear =
fromPrefixReader "linear" 0
(App.lift2
(\x0 x1 phase -> Interpol.combine2 phase (x0,x1))
getNode getNode)
cubic :: (Field.C t, Interpol.C t y) => T t y
cubic =
fromPrefixReader "cubicAlt" 1 $ App.lift4
(\xm1 x0 x1 x2 t ->
let (am1, a0, a1) = cubicHalf t
( b2, b1, b0) = cubicHalf (1t)
in Interpol.scale (am1,xm1)
+.* (a0+b0,x0)
+.* (a1+b1,x1)
+.* (b2,x2))
getNode getNode getNode getNode
cubicHalf :: (Field.C t) => t -> (t,t,t)
cubicHalf t =
let c = (t1)^2
ct2 = c*t/2
in (ct2, c*(1+2*t), ct2)
piecewise :: (Interpol.C t y) =>
Int -> [t -> t] -> T t y
piecewise center ps =
cons (length ps) (center1) $
\t ->
combineMany
"Interpolation.element: list of functions empty"
"Interpolation.element: list of samples empty" $
Sig.map ($t) $ Sig.fromList $ reverse ps
piecewiseConstant :: (Interpol.C t y) => T t y
piecewiseConstant =
piecewise 1 [const 1]
piecewiseLinear :: (Interpol.C t y) => T t y
piecewiseLinear =
piecewise 1 [id, (1)]
piecewiseCubic :: (Field.C t, Interpol.C t y) => T t y
piecewiseCubic =
piecewise 2 $
Ctrl.cubicFunc (0,(0,0)) (1,(0,1/2)) :
Ctrl.cubicFunc (0,(0,1/2)) (1,(1,0)) :
Ctrl.cubicFunc (0,(1,0)) (1,(0,1/2)) :
Ctrl.cubicFunc (0,(0,1/2)) (1,(0,0)) :
[]
function :: (Interpol.C t y) =>
(Int,Int)
-> (t -> t)
-> T t y
function (left,right) f =
let len = left+right
ps = Sig.take len $ Sig.iterate pred (pred right)
in cons len left $
\t ->
combineMany
"Interpolation.function: empty function domain"
"Interpolation.function: list of samples empty" $
Sig.map (\x -> f (t + fromIntegral x)) ps
combineMany ::
(Interpol.C a v) =>
String -> String ->
Sig.T a -> Sig.T v -> v
combineMany msgCoefficients msgSamples ct xt =
Sig.switchL (error msgCoefficients)
(\c cs ->
Sig.switchL (error msgSamples)
(curry (Interpol.combineMany (c,cs)))
xt)
ct