[Haskell-cafe] Yampa vs. Reactive

Thomas Davie tom.davie at gmail.com
Thu Dec 18 11:53:24 EST 2008


Hi Henrik,

On 18 Dec 2008, at 14:26, Henrik Nilsson wrote:

> Hi Tom,
>
> > I'll have an attempt at addressing the questions, although I freely
> > admit that I'm not as "into" Reactive as Conal is yet, so he may  
> come > and correct me in a minute.
> > [...]
> > Reactive has explicitly parameterized inputs.  In your robot  
> example I > would expect something along the lines of
> >
> > data RobotInputs =
> >     RI {lightSensor :: Behavior Colour;
> >         bumbSwitch :: Event ()} -- A couple of example robot sensors
> >
> > robotBehavior :: RobotInputs -> Behavior Robot
> > robotBehavior sensors = a behovior that combines the light sensor  
> and > the bumb switch to stay in the light, but not keep driving into
> > things.
>
> This looks exactly like Classical FRP.
> And if it is like Classical FRP behind the scenes, it nicely
> exemplifies the problem.
>
> In Classical FRP, Behavior is actually what I would call a signal
> function. When started (switched into), they map the system input
> signal from that point in time to a signal of some particular type.
>
> So, the record RobotInputs is just a record of lifted projection
> functions that selects some particular parts of the overall system
> input. Behind the scenes, all Behaviors are connected to the one
> and only system input.

I don't think this is really true.  Behaviors and Events do not reveal  
in their type definitions any relation to any system that they may or  
may not exist in.  A Behavior can exist wether or not it is being run  
by a particular legacy adapter (a piece of code to adapt it to work as  
expected on a legacy, imperative computer).  I can define an Event e =  
(+1) <$ atTimes [0,10..] and use it as a Haskell construct without  
needing any system at all to run it within.  Similarly I can define a  
Behavior b = accumB 0 e that depends on this event, completely  
independant of any system, or definition of what basic events and  
behaviors I get to interact with it.

> > data UIInputs = UI {mousePoint :: Behavior Point; mouseClick ::  
> Event
> > (); ...}
> >
> > world :: UIInputs -> Behavior World
> > world = interpret mouse and produce a world with barriers, robots  
> and > lights in it
>
> Fine, of course, assuming that all behaviours share the same kind
> of system input, in this case UI input.
>
> But what if I want my reactive library to interface to different kinds
> of systems? The robot code should clearly work regardless of whether
> we are running it on a real hardware platform, or in a simulated
> setting where the system input comes form the GUI. In Classical FRP,
> this was not easily possible, because all combinators at some level
> need to refer to some particular system input type which is hardwired
> into the definitions.

There are no hardwired definitions of what inputs I'm allowed to use  
or not use.  If I would like my reactive program to run on a "legacy"  
robot which uses imperative IO, then I may write a legacy adapter  
around it to take those IO actions and translate them into Events and  
Behaviors that I can use.  One such legacy adapter exists, called  
reactive-glut, which ties glut's IO actions into reactive events one  
can use.  I could easily imagine several others, for example one that  
interacts with robot hardware and presents the record above to the  
behaviors it's adapting, or another still which works much like the  
"interact" function, but instead of taking a String -> String, takes  
an Event Char -> Event Char.

> Had Haskell had ML-style parameterized modules,
> that would likely have offered a solution: the libraries could
> have been parameterized on the system input, and then one could obtain
> say robot code for running on real hardware or in a simulated
> setting by simply applying the robot module to the right kind of
> system input.
>
> An alternative is to parameterize the behaviour type explicitly on
> the system input type:
>
>    Behavior sysinput a
>
> This design eventually evolved into Arrowized FRP and Yampa.
>
> So, from your examples, it is not clear to what extent Reactive
> as addressed this point. Just writing functions that maps behaviours
> to behaviours does not say very much.
>
> On a more philosophical note, I always found it a bit odd that if
> I wanted to write a function that mapped a signal of, say, type "a",
> which we can think of as
>
>    type Signal a = Time -> a
>
> to another signal, of type "b" say, in Classical FRP, I'd have to  
> write
> a function of type
>
>    Behavior a -> Behavior b
>
> which really is a function of type
>
>    (Signal SystemInput -> Signal a) -> (Signal SystemInput -> Signal  
> b)

> I find this unsatisfying, as my mapping from a signal of type a to
> a signal of type b is completely independent from the system
> input (or the function wouldn't have a polymorphic type).

Yes, certainly that would be unsatisfactory.  But I don't agree about  
the type of the function -- this really is a (Time -> a) -> (Time ->  
a).  It may be though that the argument (Time -> a) is a system input  
from our legacy adapter, or an internal part of our program.

> > > * A clear separation between signals, signal functions, and  
> ordinary
> > >   functions and values, yet the ability to easily integrate all
> > >   kinds of computations.
> >
> > I agree and disagree here (that'll be the matter of taste creeping
> > in).  I agree that in Reactive you often spend a lot of keystrokes
> > lifting pure values into either an Event or a Behavior.  Having said
> > that I'd argue that Yampa requires us to do this too -- it merely
> > enforces the style in which we do it (we must do it with arrows).
>
> Yes, there is lifting in Yampa, but the arrow syntax mostly does it  
> for
> the programmer, which in practice (in my experience) translates to a  
> lot
> less effort, and, in my opinion, leads to clearer code as it is easy  
> to
> maintain a distinction between signals and static values. After all,  
> why
> should I want to live a constant to a signal, if all I'm going to do
> with it is to apply one and the same function to it over and over?
>
> (I'm not worried about efficiency here, that can be fixed: it's
> a philosophical point.)

I'm not sure I understand you clearly.  If I wish to apply a constant  
function to a signal, can I not just use fmap?

> Also, form practical experience when programming with Classical FRP,
> we often lifted entire libraries we wanted to use to avoid having
> to write explicit lifts all the time. Tedious, but OK, doable.
>
> However, quite often we then discovered that actually, we needed the
> unlifted version of the library too, leading to name clashes and
> thus extra noise to do the need to disambiguate, be it by qualified
> input or naming the lifted versions differently.
>
>
> Not a show stopper by any means, but a tedious extra level of  
> concerns.
>
> The arrow framework offer clear guidance in this case which translates
> to convenient coding practice: just use whatever library
> you need and let the arrow syntax take care of liftings where
> necessary.
>
> > My personal opinion on this one is that I prefer the applicative
> > interface to the arrow based one, because it feels more like just
> > writing a functional program.
>
> It is true that the arrow syntax sometimes is a bit too "linear". For
> example, if (without using the basic arrow combinators), I want to  
> apply
> first one function sf1 and then another sf2 to some signal x, one
> might write
>
>    y <- sf1 -< x
>    z <- sf1 -< y
>
> whereas
>
>    z = sf1 (sf2 x)
>
> would arguably be clearer in a case like this.
>
> On balance, though, I find that the advantages of the arrow framework
> outweighs such inconveniences.
>
> (Of course, one can also write
>
>    z <- sf2 <<< sf1 -< x

Or one could write z = sf2 <$> (sf1 <$> x) in Reactive --  
unfortunately, we pay the penalty of having to use a bulkier syntax  
for application than just ' ', but it still works rather nicely.  I  
agree that the arrow notation is nice in some circumstances, but my  
(admitedly limited) experience with Yampa left me often finding that I  
wanted to express something much more simply, and less sequentially  
without the arrows.

> And I think the arrow syntax likely could be tweaked to allow
> something more similar to the second version, but that's of course
> beside the point.)
>
> > I reserve judgement at the moment because I haven't explicitly  
> written
> > a reactive program involving a collection of behaviors, having said
> > that, I see no reason why removing a value from the list in a  
> Behavior > [a], it should not get garbage collected.
>
> But just the possibility of have list output is not sufficient.
>
> What is needed is a way to run a collection of independent  
> behaviours in
> parallel. Classical FRP provided essentially the following  
> functionality
> for this purpose:
>
>    [Behavior a] -> Behavior [a]

Certainly, I can imagine something along the lines of
listB = foldr (liftA2 (:)) (pure []) -- there's that lifting creaping  
in.

> This is fine, until we get to a point where we want to remove
> one of those behaviors without disturbing the others.
>
> In Classical FRP, the only thing that could be done was to
> apply a filter to the output list to *hide* the output(s) from some
> of the behaviours from the outside world. But this only makes it
> *look* as if they're gone. In fact, they're still there, consuming
> computational resources, and can be resurrected at any point.
>
> Yampa provides a way of maintaining dynamic collections of signal
> functions, allowing new signal functions to be started and others
> to be removed without affecting the other signal functions in the
> collection.
>
> It is still unclear to me if Reactive offers anything similar.
> In principle, just looking from the outside, I cannot see why reactive
> couldn't do something similar to Yampa or possibly adopt some other
> design to the same effect. But my understanding is that Reactive has
> a fairly elaborate run-time machinery behind the scenes, and I don't
> know if that would get in the way or not.

You would certainly need to ask Conal on this point, but I have no  
reason to suspect that b' = [1,2,3,4,5] `stepper` listE [(1,[])] would  
not deallocate the first list once it had taken its step.

> > > * There was also an issue with Classical FRP having to do with the
> > >  need to observe the output from one part of the system in
> > >  another part of the system.
> >
> > My understanding is that Conal went to great lengths to make sure  
> that > Behaviors get correctly cached, so that incremental values  
> are only
> > evaluated once, but I'm affraid I can't answer this more sensibly.
>
> This is a semantical issue, not one about efficiency.
>
> The question is this. Suppose we define
>
>   let
>      n :: Behavior Int
>      n = <behaviour that counts left mouse button clicks>
>   in
>      n `until` <some event> -=> n
>
> I'm not sure I got the syntax right. But the idea is that we
> output the number of left mouse button clicks, and then at some
> point, we switch to a behavior that again output the number of left
> mouse button clicks, notionally the "same" one "n".
>
> The question is, after the switch, do we observe a count that
> continues from where the old one left off, i.e. is there a
> single *shared* instance of "n" that is merely being *observed*
> from within the two "branches" of the switch, or is the counting
> behavior "n" restarted (from 0) after the switch?

Yes, we really do get a shared n -- without doing that we certainly  
would see a large space/time leak.

> In Classical FRP, the answer is the latter (because "n" really
> is a signal function mapping system input to an signal carrying
> integer counts).

Yep, in Reactive, a signal function is a

newtype BehaviorG tr tf a = Beh { unBeh :: (R.ReactiveG tr :. Fun tf)  
a }

i.e. it's a Reactive value containing functions of time.  Each mouse  
click event would create a new step in the Reactive value, allowing  
(a) the old step to be garbage collected, (b) the value for the  
current number of mouse clicks to be cached.

What may be a problem, is if we do not look at our mouse-click  
counting behavior for a long time, we may spend a lot of time when we  
do look at it, computing all of the (+1)s we have built up (but only  
once).

> Sometimes that's what one wants, other times not. Which is what
> motivated the "running in" design to effectively allow a single
> instance of a behavior to be created, whose output then could
> be observed within the scope of the definition thus avoiding
> restarting the behavior after each switch. But this design
> became very complicated, and also somewhat confusing as there
> was no type distinction between "running behaviors" (effectively
> signals) and behaviors (signal functions).

Yep, such Behaviors are seperated in Reactive only by the method you  
create them with.  I may use the `stepper` function to create a  
behavior that increases in steps based on an event occurring, or I may  
use fmap over time to create a continuously varying Behavior.

> > Your email triggered to think about a couple of the other  
> significant > differences between Yampa and Reactive
> > * Reactive deals with continuous functions of time, not sampled  
> ones.  > This allows for asynchronous sampling, for example the  
> ability to
> > sample a Behavior at 1/60th of a second rate for screen refreshes,
> > while sampling the same behavior also at 1/10th second for logging,
> > and 1/1000th for euler integration of un-integratable Behaviors.
>
> I'm not quite sure what you're getting at here.
>
> On the one hand, Yampa also notionally has continuous time.
> On the other hand, ANY implementation will have to do sampling
> at some point.
>
> But I suppose what you're saying is that Reactive allows different
> part of a system to be sampled at different rates in a transparent
> manner?
>
> Which is nice.
>
> But the tradeoffs are not clear to me.

Yes, indeed reactive allows different sample rates as you say.  The  
key though is that reactive itself does not ever do any sampling.  The  
user may create Events, and snapshot Behaviors at the times that the  
Events occur, but reactive will never explicitly say "I am going to  
sample now".  What may happen, is that the legacy adapter may have a  
built in Event at which it samples for (for example) screen refreshes.

> > * Reactive is push based.  The result of this is that we will not
> >   waste CPU cycles for example refreshing the screen when nothing  
> has
> >   changed on the output.
>
> The optimizations of Yampa also achieves a fair amount of "pushing".
> But granted, Yampa is fundamentally pull-based.
>
> That said, for truly hybrid systems, that do a lot of continuous
> computation, it is not at all clear that push is a clear winner.

Yes, I agree.  This is one of the things I'll be interested to  
discover, working with Reactive, is exactly when we have problems with  
the push based semantics.

> Only extensive benchmarking can really provide genuine insight
> into the actual pros and cons here of different FRP implementations
> for various applications, I'd say.
>
> Also, when there is a need to combine output from different
> parts of a system, and this is done by combining the various
> outputs into a tuple or record, then one have to push combined
> output whenever any one of the constituent parts changes, which
> means one lose track of the changes down the line, possibly
> resulting in redundant computations anyway.

I'm not certain that this is the case.  I *hope* that the caching in  
the Behaviors is enough that this computation is avoided, but I'm not  
100% certain.

I hope I got more on top of the problems you were pointing out this  
time.

Thanks

Tom Davie


More information about the Haskell-Cafe mailing list