module Synthesizer.Causal.ToneModulation (
ToneModS.interpolateCell,
seekCell,
oscillatorCells,
oscillatorSuffixes,
integrateFractional,
integrateFractionalClip,
limitRelativeShapes,
limitMinRelativeValues,
) where
import qualified Synthesizer.Basic.ToneModulation as ToneMod
import qualified Synthesizer.Basic.Phase as Phase
import qualified Synthesizer.State.ToneModulation as ToneModS
import qualified Synthesizer.Interpolation as Interpolation
import qualified Synthesizer.Causal.Oscillator.Core as Osci
import qualified Synthesizer.Causal.Process as Causal
import qualified Synthesizer.Generic.Signal as SigG
import Control.Arrow (first, (<<<), (<<^), (^<<), (&&&), (***), )
import Control.Monad.Trans.State (state, )
import Data.Tuple.HT (mapFst, )
import qualified Algebra.RealField as RealField
import qualified Algebra.Ring as Ring
import qualified Algebra.Additive as Additive
import NumericPrelude.Numeric
import NumericPrelude.Base
import Prelude ()
oscillatorCells :: (RealField.C t, SigG.Transform sig y) =>
Interpolation.Margin ->
Interpolation.Margin ->
Int -> t -> sig y -> (t, Phase.T t) ->
Causal.T (t,t) ((t,t), ToneModS.Cell sig y)
oscillatorCells
marginLeap marginStep periodInt period sampledTone (shape0, phase) =
seekCell periodInt period
^<< oscillatorSuffixes marginLeap marginStep
periodInt period sampledTone (shape0, phase)
seekCell :: (RealField.C t, SigG.Transform sig y) =>
Int -> t ->
((t, Phase.T t), sig y) ->
((t,t), ToneModS.Cell sig y)
seekCell periodInt period =
(\(sp,ptr) ->
let (k,q) = ToneMod.flattenShapePhase periodInt period sp
in (q, ToneModS.makeCell periodInt $
SigG.drop (ToneModS.checkNonNeg $ periodInt+k) ptr))
oscillatorSuffixes :: (RealField.C t, SigG.Transform sig y) =>
Interpolation.Margin ->
Interpolation.Margin ->
Int -> t ->
sig y -> (t, Phase.T t) ->
Causal.T (t,t) ((t, Phase.T t), sig y)
oscillatorSuffixes
marginLeap marginStep periodInt period sampledTone (shape0, phase) =
let margin =
ToneMod.interpolationNumber marginLeap marginStep periodInt
ipOffset =
periodInt +
ToneMod.interpolationOffset marginLeap marginStep periodInt
(shape0min, shapeLimiter) =
limitMinRelativeValues (fromIntegral ipOffset) shape0
((skip0,coord0), coordinator) =
integrateFractional period (shape0min, phase)
in (\(((b,n),ptr), sp@(_,p)) ->
(if b
then (zero, Phase.increment (fromIntegral n / period) p)
else sp,
ptr))
^<<
(Causal.scanL
(\ ((_,n),ptr) d -> dropMargin margin (n+d) ptr)
(dropMargin margin (skip0 ipOffset) sampledTone)
***
Causal.consInit coord0)
<<<
coordinator
<<<
Causal.first shapeLimiter
dropMargin :: (SigG.Transform sig y) =>
Int -> Int -> sig y -> ((Bool, Int), sig y)
dropMargin margin n xs =
mapFst ((,) (SigG.lengthAtMost (margin+n) xs)) $
SigG.dropMarginRem margin (ToneModS.checkNonNeg n) xs
regroup :: (Int,t) -> Phase.T t -> ToneMod.Skip t
regroup (d,s) p = (d, (s,p))
integrateFractional :: (RealField.C t) =>
t ->
(t, Phase.T t) ->
(ToneMod.Skip t, Causal.T (t,t) (ToneMod.Skip t))
integrateFractional period (shape0, phase) =
let sf0 = splitFraction shape0
shapeOffsets =
Causal.fromState
(\c -> state $ \s0 ->
let s1 = splitFraction (s0+c)
in (s1, snd s1))
(snd sf0)
scale (n,_) = fromIntegral n / period
phase0 = Phase.decrement (scale sf0) phase
phases =
Osci.freqModSync phase0
<<^ (\(s,f) -> f scale s)
in (regroup sf0 phase0,
uncurry regroup
^<<
(Causal.map fst &&& phases)
<<<
first shapeOffsets)
integrateFractionalClip :: (RealField.C t) =>
t ->
(t, Phase.T t) ->
Causal.T (t,t) (ToneMod.Skip t)
integrateFractionalClip period (shape0, phase) =
let sf0 = splitFraction shape0
shapeOffsets =
Causal.fromState
(\c -> state $ \s0 ->
let s1 = splitFraction (s0+c)
in (s1, snd s1))
(snd sf0)
scale (n,_) = fromIntegral n / period
phases =
Osci.freqMod
(Phase.decrement (scale sf0) phase)
<<^ (\(s,f) -> f scale s)
in uncurry regroup
^<<
((Causal.consInit sf0 <<^ fst) &&& phases)
<<<
first shapeOffsets
limitRelativeShapes :: (Ring.C t, Ord t) =>
Interpolation.Margin ->
Interpolation.Margin ->
Int -> t -> (t, Causal.T t t)
limitRelativeShapes marginLeap marginStep periodInt =
limitMinRelativeValues $ fromIntegral $
ToneMod.interpolationOffset marginLeap marginStep periodInt + periodInt
limitMinRelativeValues :: (Additive.C t, Ord t) =>
t -> t -> (t, Causal.T t t)
limitMinRelativeValues xMin x0 =
let x1 = xMinx0
in if x1<=zero
then (x0, Causal.id)
else (xMin,
Causal.crochetL
(\x lim -> Just $
let d = xlim
in if d>=zero
then (d,zero) else (zero, negate d)) x1)