module Synthesizer.Generic.Control (
constant,
linear,
linearMultiscale,
linearMultiscaleNeutral,
line,
exponential, exponentialMultiscale,
exponentialMultiscaleNeutral,
exponential2, exponential2Multiscale,
exponential2MultiscaleNeutral,
vectorExponential,
vectorExponential2,
cosine, cosineMultiscaleLinear,
cosineMultiscale,
Ctrl.cosineWithSlope,
cubicHermite,
) where
import qualified Synthesizer.Plain.Control as Ctrl
import qualified Synthesizer.Generic.Signal as SigG
import qualified Algebra.Module as Module
import qualified Algebra.Transcendental as Trans
import qualified Algebra.Field as Field
import qualified Algebra.Additive as Additive
import qualified Number.Complex as Complex
import Number.Complex (cis,real)
import NumericPrelude.Numeric
import NumericPrelude.Base
constant :: (SigG.Write sig y) =>
SigG.LazySize -> y -> sig y
constant = SigG.repeat
linear :: (Additive.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
linear size d y0 = SigG.iterate size (d+) y0
linearMultiscale ::
(Additive.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
linearMultiscale size =
curveMultiscale size (+)
linearMultiscaleNeutral :: (Additive.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> sig y
linearMultiscaleNeutral size slope =
curveMultiscaleNeutral size (+) slope zero
line :: (Field.C y, SigG.Write sig y) =>
SigG.LazySize
-> Int
-> (y,y)
-> sig y
line size n (y0,y1) =
SigG.take n $ linear size ((y1y0) / fromIntegral n) y0
exponential, exponentialMultiscale ::
(Trans.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
exponential size time =
SigG.iterate size (* exp ( recip time))
exponentialMultiscale size time =
curveMultiscale size (*) (exp ( recip time))
exponentialMultiscaleNeutral :: (Trans.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> sig y
exponentialMultiscaleNeutral size time =
curveMultiscaleNeutral size (*) (exp ( recip time)) one
exponential2, exponential2Multiscale :: (Trans.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
exponential2 size halfLife =
SigG.iterate size (* 0.5 ** recip halfLife)
exponential2Multiscale size halfLife =
curveMultiscale size (*) (0.5 ** recip halfLife)
exponential2MultiscaleNeutral :: (Trans.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> sig y
exponential2MultiscaleNeutral size halfLife =
curveMultiscaleNeutral size (*) (0.5 ** recip halfLife) one
vectorExponential ::
(Trans.C y, Module.C y v, SigG.Write sig v) =>
SigG.LazySize
-> y
-> v
-> sig v
vectorExponential size time y0 =
SigG.iterate size (exp (1/time) *>) y0
vectorExponential2 ::
(Trans.C y, Module.C y v, SigG.Write sig v) =>
SigG.LazySize
-> y
-> v
-> sig v
vectorExponential2 size halfLife y0 =
SigG.iterate size (0.5**(1/halfLife) *>) y0
cosine, cosineMultiscaleLinear :: (Trans.C y, SigG.Write sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
cosine size = Ctrl.cosineWithSlope $
\d x -> SigG.map cos (linear size d x)
cosineMultiscaleLinear size = Ctrl.cosineWithSlope $
\d x -> SigG.map cos (linearMultiscale size d x)
cosineMultiscale ::
(Trans.C y, SigG.Write sig (Complex.T y),
SigG.Transform sig (Complex.T y), SigG.Transform sig y) =>
SigG.LazySize
-> y
-> y
-> sig y
cosineMultiscale size = Ctrl.cosineWithSlope $
\d x -> SigG.map real (curveMultiscale size (*) (cis d) (cis x))
cubicHermite :: (Field.C y, SigG.Write sig y) =>
SigG.LazySize
-> (y, (y,y)) -> (y, (y,y)) -> sig y
cubicHermite size node0 node1 =
SigG.map (Ctrl.cubicFunc node0 node1) $ linear size 1 0
curveMultiscale :: (SigG.Write sig y) =>
SigG.LazySize -> (y -> y -> y) -> y -> y -> sig y
curveMultiscale size op d y0 =
SigG.cons y0 . SigG.map (op y0) $ SigG.iterateAssociative size op d
curveMultiscaleNeutral :: (SigG.Write sig y) =>
SigG.LazySize -> (y -> y -> y) -> y -> y -> sig y
curveMultiscaleNeutral size op d neutral =
SigG.cons neutral $ SigG.iterateAssociative size op d