Reactimate - A new AFRP library

Here’s how I would write that shepard example from the paper in a normal applicative FRP style:

shepard :: Time -> Behavior Double
shepard seconds = if seconds <= 0.0
  then pure 0.0
  else
    let f = envLineSeg [800, 100, 100] [4.0, seconds]
        e = envLineSeg [0, 1, 0, 0] [2.0, 2.0, seconds]
        s = osc sineTable 0 f
        r = delayLine 0.5 (shepard (seconds − 0.5))
    in (e * s * 0.1) + r

Of course I guess the real question is how I’d implement these abstractions. That will take some more time. And the paper doesn’t seem to say what envLineSeg is any way.

Edit:

Actually, it is not so hard to implement it with a free applicative (click to see code)
import Control.Applicative

type Time = Double

type Vector = []

type Table = Vector Double

data Behavior a where
  EnvLineSeg :: [a] -> [Time] -> Behavior a
  Osc :: Table -> Double -> Behavior Double -> Behavior Double
  DelayLine :: Time -> Behavior a -> Behavior a
  Ap :: Behavior (b -> a) -> Behavior b -> Behavior a
  Pure :: a -> Behavior a
instance Functor Behavior where
  fmap = liftA
instance Applicative Behavior where
  pure = Pure
  (<*>) = Ap
instance Num a => Num (Behavior a) where
  (*) = liftA2 (*)
  (+) = liftA2 (+)
  fromInteger = pure . fromInteger
  abs = fmap abs
  signum = fmap signum
  (-) = liftA2 (-)
instance Fractional a => Fractional (Behavior a) where
  fromRational = pure . fromRational
  (/) = liftA2 (/)

sineTable :: Table
sineTable = undefined

shepard :: Time -> Behavior Double
shepard seconds = if seconds <= 0.0
  then Pure 0.0
  else
    let f = EnvLineSeg [800, 100, 100] [4.0, seconds]
        e = EnvLineSeg [0, 1, 0, 0] [2.0, 2.0, seconds]
        s = Osc sineTable 0 f
        r = DelayLine 0.5 (shepard (seconds - 0.5))
    in (e * s * 0.1) + r

indexOfCumulative :: Double -> [Double] -> Int
indexOfCumulative = undefined

sample :: Time -> Behavior a -> a
sample t (EnvLineSeg xs ts) = xs !! indexOfCumulative t ts
sample t (Osc table what ever) = undefined
sample t (DelayLine d x) = if t < d then 0 else sample (t - d) x
sample _ (Pure x) = x
sample t (Ap f x) = sample t f $ sample t x
1 Like