Reactimate - A new AFRP library

As I see it, the point of using arrows isn’t to enable dynamic switching. The static nature of the Arrow interface enables optimizing the computation ahead of running it (assuming the concrete type implementing the interface is concerned with this), and arrow-style feedback loops offer very concise management of local state.

The dynamic switch at least as it is formulated in Yampa gives a Monad-like interface on top of signal functions:

switch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b

Much like Monad, the dynamic nature of this gives maximum flexibility because the network structure can be reconfigured on the fly. This comes at a cost of not being able to optimize the whole network ahead of time though, which is something a more constrained framework like CCA is able to achieve.

While FRP without dynamic switching is not as powerful as FRP with dynamic switching by definition, there are many useful programs that can be expressed statically, especially when local state is so readily available.

1 Like

Compared to monads, arrows indeed allow more static optimization. However, if you don’t have dynamic switching then you should really compare to applicatives. Which programs can you write using CCAs that you can’t write with simple applicatives?

Programs that can be written using CCAs that can’t be written with simple applicatives are those that leverage the extra power the Arrow interface provides over Applicative. When the input of one part of a computation directly depends on the output from a previous part of the computation, then that computation can’t be expressed in an Applicative context. The computation can be expressed in Arrow or Monad contexts, but when both parts of the computation are statically known, Arrow offers just enough power to express it. The benchmarked flute and sheperd programs in the linked CCAs Revisited paper are examples that can’t be expressed in an Applicative context as far as I’m aware.

1 Like

I’m in fact not aware of any, it’s just on the long list of things I want to do eventually :sweat_smile: in the dynamic switching debate, Clash should fall in the same expressivity category like arrows (although they insist on writing as much as possible with Applicative).

Sounds like a blend between React and reanimate.

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