[Haskell-cafe] Phase correction?

Mario Lang mlang at blind.guru
Wed Jun 8 19:17:08 UTC 2022


Hi.

This is more a math question then a Haskell specific thing.
However, Haskell fits nicely to write down the problem as executable
"pseudo" code, so here I am, knowing that you all can read this and
actually grasp the problem at hand (which I obviously dont).
I stumbled across this while naively playing with C++ infinite ranges,
starting with std::ranges::views::iota.  So there I was, happily playing with
signal generation, until I went stuck here: Modulating oscillation
frequency while trying to stay stateless.  But code says more then a
foreign language, so:

#!/usr/bin/env stack
-- stack --resolver lts-19.8 runghc
import Data.Ratio

n = [0 ..]
d = 10 -- EXAMPLE, usually 48000
t = (% d) <$> n
sine f = (\x -> sin $ 2*pi * fromRational x * f x) <$> t
sine1 = sine $ const 1 -- OK

-- Lets devise a method to specify a value changing over time
data I = No | Lin | Exp
erp No a _ _ = a
erp Lin a b mu = (1 - mu) * a + mu * b
erp Exp a b mu = a * ((b / a) ** mu)
data Curve a = Curve a [(I, Double, a)]
at (Curve p1 []) _ = p1
at (Curve p1 ((i, d, p2):xs)) t = go 0 d p1 p2 i d xs where
  go t1 t2 p1 p2 i d xs
    | t < t2 = erp i p1 p2 $ (t - t1) / d
    | null xs = p1
    | (i', d', p2') <- head xs = go t2 (t2 + d') p2 p2' i' d' $ tail xs

-- Frequency modulation?
c = Curve 1 [(Exp, 1.0, 2), (Exp, 1.0, 1)]
sine2 = sine $ at c . fromRational -- WRONG!🙅
-- Whenever a change occurs, phase is incorrect
-- because current step doesn't know about the past

main = do
  print $ take 10 $ sine1
  print $ at c 0.5 == at c 1.5
  print $ take 10 $ sine2

-- The naive question of an experimenting non-math coder person is:
-- Can a version of `at` be written which compensates for the phase
-- differences which runs in O(n) where n is the number of curve points?
-- Intuitively this should be possible given `d` (denominator).
at' :: Curve a -> Ratio b -> a
at' c t = undefined

-- 
CYa,
  ⡍⠁⠗⠊⠕


More information about the Haskell-Cafe mailing list