Git Product home page Git Product logo

Comments (20)

ehird avatar ehird commented on September 26, 2024

Oh, and I forgot to add: I'm perfectly willing to put in the work to modify reactive-banana and reactive-banana-wx (plus its examples) in line with whatever, if anything, is decided.

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

First of all, thanks a lot Elliott Hird for this diligently researched issue!

The Discrete data type is a tough one. As you can probably guess from the documentation, I'm not too happy about it, and Conal Elliott was even more unhappy. I'd love to see Behavior overtaking the role of Discrete as well, but there are a few fundamental obstacles to this that I don't know how to solve. But hopefully we'll figure something out.

To set the stage, I'm going to document my rationale for the Discrete type in this really long comment and save ideas concerning solutions for the subsequent discussion. (We should probably also collect this on the wiki or something. The github wiki has the advantage that we can keep the formatting.)

Why Discrete?

Behaviors and continous time

The most fundamental feature of the Behavior is that it can describe values that vary continuously in time. The intended semantics is

type Behavior a = Time -> a

which allows things like

vehiclePosition :: Behavior Location
vehiclePosition t = velocity*t + start

where the position of the vehicle grows continuously with time. That was Conal Elliott's original vision and I'd like to stay true to it.

Ironically, this does not seem possible in reactive-banana right now, but all you need is a special behavior

time :: Behavior Time

that denotes the current time. Once you have that, you can do things like

afternoon :: Behavior Bool
afternoon = (\t -> after 12 t && before 24 t) <$> time

vehiclePosition :: Behavior Location
vehiclePosition = (\t -> velocity*t + start) <$> time

The library currently doesn't offer a time combinator, but you can obtain it by polling

clockTime :: NetworkDescription (Behavior UTCTime)
clockTime = fromPoll getCurrentTime

Voilà, now you have continous time in reactive-banana.

But computers are discrete?

Of course, there is something fundamentally strange about continuous time, namely: how do you actually implement it? I mean, computers will only ever be able to represent discrete things, so it all boils down to some small but discrete timestep, doesn't it? Mostly yes, but there is one imporant observation where the answer is no: if all you can ever do with a behavior is to evaluate it at particular points in time, then it feels like it's perfectly continuous.

In other words, the function

\time -> 2*time

is continuous, the restriction is just that computers can only sample it at a discrete set of times. We can uphold the illusion of continuous time even though computers are discrete.

This is the reason why apply is the only way to observe a Behavior in reactive-banana. And as you can see, behaviors are implement discretely in reactive-banana, yet the illusion is upheld.

If all this sounds a bit too philosophical, you can always take the stance that continuous time merely means that you can write functions that are independent of the time-step with which you will run your simulation. This is certainly desirable for writing correct software.

The case for explicit sampling

Of course, if you want to do anything fancy, like detecting flanks of a DSP signal or numerical integration, then you always have to sample your behaviors at small time steps. The library doesn't do anything magical for you. In fact, I argue that it shouldn't do anything magical: numerics with floating point numbers are tricky. Results do depend on the size of the time step, so you can't abstract it away, unfortunately; you often need explicit control to keep your numerics stable.

On a more basic level, the notion of behaviors as continuous in time means that there is no meaningful function

changes :: Behavior a -> Event a

that notifies you when the behavior has "changed". I mean, what is

changes ((\t -> 2*t) <$> time)

supposed to be? If you want to observe updates explicitely, you have to use another data type, for instance Discrete.

In fact, the Discrete data type tends to creep in naturally when programming with events. For instance, I don't use accumE anymore, I always write it as changes . accumD because I can visualize that more easily. Conal's highly experimental reactive library has a few of these as well; for instance, the zipE function is basically the applicative instance for Discrete.

Incremental updates

Of course, we mostly want to observe updates for reasons of efficiency: it's faster to redraw only part of a graphic than to draw the whole graphic. That's why we would want a changes function on the Behavior in the first place.

But the Discrete type, or a Behavior were we may observe changes, is only the beginning of efficient updates. Namely, these updates always consist of a whole value. What if we want to calculate diffs and pass those as events, i.e. if we want to program with incremental updates?

You can see incremental updates in action in the DatabaseTime type in the CRUD.hs example, and the TimeGraphic type in the old BlackBoard tree. Both types represent a value that varies in time (a database, a graphic), but their evolution is calculated in terms of an event that represents incremental updates to the value. The point is that the events don't contain new values, only changes to the original value.

Granted, the Discrete type doesn't cover these cases, but clearly, we can't shoehorn them into the existing Behavior either, because the library does not allow us to retrofit Behavior with custom incremental updates. I mean, if these custom types can't be Behavior, then I think it's only fair that Discrete can't be Behavior either. :-)

Summary

So, the problem is that

  • Code would be a lot simpler if Behavior and Discrete were one and the same.

but

  • Due to being continuous, Behavior does not support a function changes :: Behavior a -> Event a.
  • Even if we can observe changes in Behavior for the purpose of efficient sampling, we still need to develop new data types if we want to use incremental updates.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

I definitely agree that continuous time (or less abstractly timestep-independence) is very important, but I'm not sure the current Behavior can be justified with Time -> a. Even besides the fact that that model has well-known semantic junk,1 I tend to view "FRP time" as an abstract notion, detached from any real clock; since, as you said, we value and maintain timestep-independence, it seems strange to claim that maintaining the ability to explicitly depend on the timestep is an advantage of the current system!

However, if you do want to write a program with explicit time, and manage to make it timestep-independent, then my proposed solution handles this too; you just pick an arbitrary timestep for your clock:

tick <- makeClockTickEvent 0.1
clock <- fromPollB (getCurrentTime <@ tick)

(modulo the fact that tick should probably be Event UTCTime in the first place...)

Of course, you lose efficient updates. Along with the fact that I find the programming model awkward, that's why I don't like explicit time :)

I agree that, at least for now, implementations of types must be specialised to each situation to handle efficient updates, and that Discrete is essentially just the simplest possible specialised-for-updates implementation of Behavior. But the fact that these implementations themselves don't really lose anything by using Discrete, and that the vast majority of current toolkits and libraries operate in a way that fits the Discrete implementation well, mean that it is still an appealing bedrock, IMO.

Re: changes . accumD — that's not really safe, is it? Your semantics will change once issue #19 is closed. Perhaps it is slightly more clear, but it seems to me that there are better ways to make FRP programs easy to write and understand than to keep a complicating sorta-hack because an operation reads more nicely expressed with it :)

I also completely agree that exposing changes with that type for Behaviors would be terrible; the reason I suggested putting its result type in NetworkDescription is the same reason things like observable sharing happen in IO — whereas IO is the sin-bin for any side-effect we don't understand, NetworkDescription is the sin-bin for interfacing FRP to the ugly outside world :)

While my proposed changes does still deliberately break the continuous-time model (but only from within NetworkDescription), as you noted, that model has to be broken at some point anyway to interface with the real world; at least until we get FRP-based operating systems.

Although, I think it would be perfectly legitimate to implement changes as something which created an event that sampled the Behavior every 0.5s, which is perfectly compatible with an (impossible) continuous-time implementation. Perhaps my proposed form should be called sample.

Thanks for your in-depth comments so far! The explanation of Discrete is very good, I think it should definitely go on the wiki.

1 Even though the post is talking about arrowised FRP, you run into the same junk with Behavior a -> Behavior b in "classic" FRP.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Oh, and for what it's worth, I would generally attempt to keep the interfaces to things like DatabaseTime and TimeGraphic to their abstract model (which is probably just Behavior T for some T), not exposing the event, etc.; to benefit from the update notification, I would define

updates :: ... -> NetworkDescription (Event ...)
updates = return . updatesField

for the reasons I stated above.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

By the way, here is a more formal argument that an RNG cannot be represented properly as a Behavior Int:

Let us consider a Behavior Int as a function f : Time → Int, where we'll pretend Time is a real.

Consider this behaviour:

bad :: NetworkDescription (Behavior Int)
bad = do
  var <- newMVar 0
  fromPoll . modifyMVar_ var $ \(!n) -> (n+1, n)

Let's say we have an FRP implementation that samples a behaviour regularly with timestep dt. That is, it computes f(0), then f(dt), then f(2_dt_), and so on. First let's set dt = 0.5. Sampling of bad proceeds as follows:

f(0)= 0
f(0.5)= 1
f(1)= 2
f(1.5)= 3
f(2)= 4

Now let's try the same thing with dt = 0.25:

f(0)= 0
f(0.25)= 1
f(0.5)= 2
f(0.75)= 3
f(1)= 4

Oops! We have f(1) = 2, but f(1) = 4. Timestep-independence has been violated; this behaviour is defined entirely by the implementation details acting on it. Sure, it's true that with current systems, we can't avoid having the "outside world" pollute the FRP system a bit, but this behaviour is completely meaningless — all it does is observe the implementation detail of when sampling happens.

So how does this differ from an RNG?

rng :: NetworkDescription (Behavior Int)
rng = do
  gen <- getStdGen >>= newMVar
  fromPoll . modifyMVar_ gen $ \(!g) ->
    let (a, g') = random g in (g', a)

The only difference here is that the change to the state is more confusing (but no less predictable) than (+1).

You could argue that it's best to see an RNG as an input to the whole system from the outside world, and so this is legitimate; but, by going back to bad, we can see the real problem here: the input is changing, not because of some external influence, and not because of some well-defined FRP behaviour (in the English-language sense), but because of implementation details; the FRP implementation is the entire source of the time-varying behaviour, and so it is not really an input at all.

You could also argue that anything you make with fromPoll is completely lawless and anything goes. I think this would be a very unfortunate position to take, and also one inconsistent with how we treat programs; a program that used a Behavior's sampling side-effects to control the appearance and functionality of a user-facing GUI would be seen as very bad style indeed.

How can we correct this? Well, if we want the FRP system to drive the advancing of the state, why not explicitly express this with the tools it gives us?

rng :: Event () -> NetworkDescription (Behavior Int)
rng = ...

The Event controls when the RNG state is to be advanced, just as the observation of the value did in the previous, broken version. The point of all this is that, although bad and rng are not behaviours, and incidentally cannot be implemented with my proposal, the new, corrected rng can be!

rng :: Event () -> NetworkDescription (Behavior Int)
rng tick = do
  (a1, g1) <- getStdGen >>= random
  gen <- newMVar g1
  fromPollB a1 (next gen <$ tick)
  where next gen =
          modifyMVar_ gen $ \(!g) ->
            let (a, g') = random g in (g', a)

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

I'll comment a bit on your reply and then move on to API suggestions and practical considerations.

Very good point on accumE vs changes . accumD by the way, it makes me think whether simultaneous events are really a good idea, but that's for another time.

Philosophy

Concerning the semantics of fromPoll, you are right that bad depends on an implementation detail. However, it's not meaningless, you can interpret it as "the behavior that counts the number of events that the network has received". So, basically, the fromPoll function implicitely depends on an event that fires whenever the network receives an external event.

Be as it may, once you've got a behavior in the pure world, you can really think of it as a function Time->a. (That's possible because reactive-banana only offers the apply function to observe behaviors, that's why I like it a lot. Everything beyond that has to use events explicitely.) Sure, fromPoll may have created something ugly, but once it exists, it can be interpreted as a function.

Concerning the random number behavior in particular, I actually like it a lot. The thing is that the weird implementation doesn't matter so much because the numbers are supposed to be random anyway. The idea of a value that is completely randomly at each point in time is extremely appealing to me. (It's also what makes the Asteroids examples simpler.)

Put differently: fromPoll is a bit like unsafePerformIO. Sure, it can mutate underneath, but as long as the result is immutable, it's ok to use it. Likewise, the implementation of the random number behavior depends on some discrete event or time-step, but the semantics of the result - random numbers - no longer depend on that. The situation is similar for the time :: Behavior Time obtained from polling the system clock.

Implementation

Ok, so, my overall philosophy is that I am fond of the Time -> a view and want to keep that as much as possible. Of course, I want simplicity, too, so I have to compromise at one point.

Your proposal is to augment each Behavior with an event that notifies of changes, and your key idea is to make it observable only in the NetworkDescription monad sin-bin, so that we don't pollute the pure semantics too much. I like that.

API

My first question would be: when do we assign an event of changes to a Behavior? You propose to do that at creation time, with a function that uses an explicit event to sample the behavior. We would get an interface along the lines of

fromSamples1 :: Event (IO a) -> NetworkDescription (Behavior a)
-- or perhaps
fromSamples2 :: IO a -> Event () -> NetworkDescription (Behavior a)

changes :: Behavior a -> NetworkDescription (Event a)

However, another option would be to sample at observation time, giving an interface along the lines of

fromPoll :: IO a -> NetworkDescription (Behavior a)
sample   :: Behavior a -> Event () -> NetworkDescription (Event a)

The idea is that the sample function is similar to apply, except that it may fire less events than indicated, namely when the behavior hasn't changed in-between.

If we have an event that explicitely notifies us of events, we may be able to convert several of these viewpoints into each other.

networkUpdate1 :: Event ()
-- or perhaps
netwokrUpdate2 :: NetworkDescription (Event ())

Other things to ponder

One question that seems important to me but that is hard to answer is the following: how do the new Behavior interact with explicit efficient updates, like used in DatabaseTime and TimeGraphic? After all, if we want to change DatabaseTime whenever a behavior changes, we have to explicitely observe the changes to the behavior. That's where Discrete would be necessary, which would defeat the point.

Practical considerations

Especially the last question is hard to answer without writing actual code to gain experience. You seem keen on experimenting with "pimped" behaviors, so I propose that reactive-banana implements a version of the API above as soon as possible, so that we can get our hands dirty. The intention is to keep it strictly experimental1 and decide later whether it should be kept or removed.

1Though it's not like reactive-banana is any less experimental in the large, hehe.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

"the behavior that counts the number of events that the network has received" — so it would be a backwards-compatibility-breaking change for reactive-banana to avoid recomputing Behaviors that it knows aren't going to be consulted in the processing of an external event? That seems wrong to me. As does being able to count such a thing without doing something unidiomatic; while it's true that as long as an RNG gives random numbers we don't really care all that much how they're generated, can you really say that a program which reacts to optimisations in the FRP implementation like that is acceptable?

The perspective of the RNG being a function that's random at all points in time is fair, though.

Your proposed alternate API is interesting, but it has its downsides: you can't do quite the same thing you can do with a Discrete, i.e. you need to know when the updates happen to get them. But OTOH that preserves the "abstract" interface of arbitrary Behaviors, and only ones meant to be observed like that could provide their own sampling functions that uses sample under the hood.

On the other hand, this seems to require that everything that would previously use Discrete must now have its own data type wrapping it with its own operations:

makeFoo :: ... -> NetworkDescription Foo
sampleFoo :: Foo -> Event Something

— unless we don't even bother, and just offer

makeFoo :: ... -> NetworkDescription (Behavior Something, Event ())

and shift the burden of using sample to the consumer of the API. I find both of these incredibly unsatisfying; it feels like a step backwards. If we're going to build some update-related intelligence into Behavior, it should not force code to become more complex because of update handling. So, I think I'm strongly in favour of coupling the sampling event to the creation of the Behavior: a GUI toolkit knows when a text box is updated, so it can implement the abstract Behavior String using its knowledge of this. That's why Discrete exists in the first place, after all.

As for explicit efficient updates, I'm not sure I understand what you're trying to convey; what does it mean to update a DatabaseTime whenever a Behavior changes? The DatabaseTime API as it stands doesn't seem to offer any functionality for this; I'd just leave the API and implementation as-is, although I would likely hide the changesDB field and re-export a version in NetworkDescription for consistency with sample. (Incidentally, I don't see why initialDB is necessary; it's never used. If we add sample, it seems reasonable to add initial :: Behavior a -> NetworkDescription a too, which would make it completely unnecessary. Hmm, could we make sample fire when the network is actuated? It seems weird to have it be designed for rendering a Behavior to a GUI or whatever, but having to handle the special-case of the first value separately.)

I agree that it's hard to be sure about quite a few things here without trying it out, and getting a working version of reactive-banana with an API similar to all this is the best way of trying it out — a git branch replacing the current API seems like the simplest way to accomplish this without disturbing existing users. Still, it's probably best if we can agree at least broadly what the API should look like first :)

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Hmm, on further inspection of DatabaseTime and TimeGraphic, they're essentially (Behavior a, Event u) for some update type u. This started to ring a bell, and then I realised that it's because this is what DataDriven's SourceC type is. I could imagine an API where the time-varying value type takes another parameter specifying the update type, looking like:

type Behavior = Source ()
fromPoll :: IO a -> Event u -> NetworkDescription (Source u a)
sample :: Source u a -> NetworkDescription (Event u)

This is tantalisingly close to my preferred version of fromPoll; implementing it would, I think, be just as easy. The question would then be whether this covers all forms of incremental updates (it handles all the ones I've seen so far, at least), and how nice it is to use in general (which only experimentation could answer).

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Hmm, could we make sample fire when the network is actuated? It seems weird to have it be designed for rendering a Behavior to a GUI or whatever, but having to handle the special-case of the first value separately.

At the risk of saying way too much at once, I wonder if the upcoming starting times of Events and Behaviors makes this more meaningful?

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

(Headers for easier reading.)

fromPoll

Good point, my proposed interpretation of the result of fromPoll is bogus. I guess the point is that the action may only read data, not change it. Only then is fromPoll going to yield a "morally" well-behaved behavior.

Sampling at observation time

Concerning the sampling at observation time

sampleLate :: Behavior a -> Event () -> NetworkDescription (Event a)

the idea would be that you supply an event that happens very frequently as second argument, but the library will just remove most occurrences because the behavior has not changed. So, internally, the library does keep track of when a behavior changes, but the API only allows you to query whether a behavior did not change between two event occurrences. I think this is good enough for rendering: most of the time, nothing changes, but you've also specified a maximum frames per second in the case where the behavior changes continuously.

So, this would be slightly less powerful than sampling at creation time as you suggest, but it's also closer to the Time -> a spirit. Can we express the less powerful API in terms of the more powerful API? This would give us the option to have both at once.

Incremental updates

Concerning incremental updates, I agree that the viewpoint

data Source u a ~ (Behavior a, Event u)

is the right way to think about it. And now I remember why I discarded this as a primitive type: Source u is no longer an applicative functor, there is no general method to combine different update types. It works special cases like u = a or u = (), but I don't see a generic way to write an applicative instance.

Bidirectional controls

Oh, and now I finally remember one of my main reasons why I didn't try to include update events in Behavior: bidirectional controls may produce to feedback loops. I made the CurrencyConverter example specifically to highlight this issue.

The example works like this: you can write numbers in either text entries and the other entry will update accordingly. Clearly, you can't do something like this

mdo $
    bEuro <- poll entryEuro text
    sink entryEuro [ text :== convertFrom bDollar ]

    bDollar <- poll entryDollar text
    sink entryDollar [ text :== convertTo bEuro ]

because then, an update to one text entry will cause an update to the other text entry, which will etc.

Hm, but it seems that the solution is simply as the example shows: the feedback cycle is broken by explicitely sampling the text values only on the keyboardUp event. In other words, any potential update events of the behavior are simply discarded.

Where to get updates from?

But the example shows another problem: I don't actually know how to get update events for properties like text from wxHaskell. :-(

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Sampling at observation time

It's an interesting idea, although one seemingly incompatible with the incremental-updates-in-Behavior style (you need to specify the change event at construction time). Still, I strongly suspect that the kind of Behaviors we actually want to sample like that will all have updates, and so will universally be called with some very fast Event to get things going, which seems awkward and also limits the frame-rate unnecessarily. networkUpdate solves the latter, but it worryingly reminds me of the "dense events" you get with the original arrowised FRP model.

Incremental updates

Well, it is Applicative, isn't it? Using the tuple definition:

instance Applicative (Source u) where
  pure a = (pure a, never)
  (fb, fu) <*> (xb, xu) = (fb <*> xb, union fu xu)

Of course, this doesn't help for combining Source u (a -> b) and Source v a into Source ??? b.

-- most general, ugliest
app :: Source u (a -> b) -> Source v a -> Source (Either u v) b

-- probably least useful, using mempty when argument updates
appL :: (Monoid u) => Source u (a -> b) -> Source v a -> Source u b

-- probably most useful (I wager most applications of Behaviors are to a pure function)
-- using mempty when function updates
appR :: (Monoid v) => Source u (a -> b) -> Source v a -> Source v b

These are all pretty ugly, though. I'm pretty sure the two incremental update types are always applied in argument position, but that doesn't say much. A horrible typeclass hack could be used to allow us to use app everywhere and just extract the type we want out of it without unwrapping a billion layers, but (a) you can't fold nicely with app (although the Applicative instance would probably work there) and (b) error messages would become incomprehensible.

Hmm. I had an idea to use something like

fromPoll :: Event u -> IO a -> NetworkDescription (Behavior a, Key u)
sample :: Behavior a -> NetworkDescription (Event Vault)

which allows all the instances and the like, but has the same essential problem that you're going to need to put the Key u somewhere and so will end up wrapping Behavior in yet another newtype.

I'm not sure what to do here; we could backtrack to the Source ()-equivalent, but it seems like it's missing so many nice capabilities compared to this that it would be a waste to devote the effort to it.

I looked at the source of the DataDriven paper to see how it solved this (unfortunately all the links to the DataDriven source code itself seem broken).

In fact, the Functor and Applicative instances for Source rely on very little about the choice of IO and Notifier, so they can be stated much more generally.

type DataDriven nfr xtr = (,) nfr `O` xtr
type Source = DataDriven Notifier Extractor

With this refactoring, DataDriven nfr xtr is an AF for any monoid nfr and applicative functor xtr.

Perhaps all we need is something like mapUpdate :: (u -> v) -> Source u a -> Source v a to make the Source u Applicative be enough. I think that requiring the update type be a monoid is a good idea; for instance, it's required for my "update event fires at the very beginning" idea. (It also gives us mappend, but I don't think it's of much use; simultaneous updates can be simultaneous events.)

As another perspective, when applying things to the Behavior denoting the current value of a graphic or a database, the incremental updates to those will be meaningless to the resulting Behavior. So you could even argue for

app' :: Source u (a -> b) -> Source v a -> Source () b

Hmm... we could tie update types to the value type. but we'd need a Monoid constraint, and thus something like the restricted monad typeclasses for Applicatives. Nah.

Bidirectional controls

The most popular solution for this is an infinitesimal delay, isn't it? The problem then is that you have to specify a junk value to be used for the first instant...

Where to get updates from?

I looked into this. wxWidgets appears to be badly-designed enough that updates to state are decoupled from the events that cause them, and there is seemingly no way to hook into a property changing,1 so the only practical solution is for reactive-banana-wx to get a little bit more manual in its types:

behavior :: w -> WX.Attr w a -> WX.Event w (IO ()) -> NetworkDescription (Behavior a)

or something of the sort. This is unquestionably an ugly pain, but I believe this is something you'd need anyway for sufficiently advanced wxWidgets programs; specifying every single way one specific piece of state can change every time doesn't scale. At least this shifts the ugliness into the the real-world glue, rather than the event network itself.

Conclusion

Hmm, I seem to be less sure of where to go than I was last time :)

My preferred solution by a long way is to make something like Source which captures incremental updates work. If that really, truly isn't possible, then non-incremental updates of a Behavior is still better than the current situation.

1 GTK+ offers this, for instance.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Sorry, my interpretation of DataDriven is incorrect; it takes a monoid, but that monoid is usually DataDriven's equivalent of Event u, which is a monoid even if the actual update type isn't.

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

Moving forward

I thought of a way to start experimenting with this stuff right away. It appears to that pretty much all the functionality here can be implemented in terms of the old types as

type Behavior a = Old.Discrete a
type Event a    = Old.Event a

As issue #26 indicates, I will try to reorganize the interace a bit, so that we can experiment with different semantics and interfaces.

Sampling at observation time

With a push-driven implementation, the networkUpdate function would work just fine; expensive calculations are only done when the behavior has actually changed. But yeah, it's probably silly.

Incremental updates

Hm, nothing that stands out as particularly elegant yet, but I agree that this problem is definitely worth solving in the long run, even independent of the implementation of Behavior. I think the best way to make progress here is to learn from examples. Hopefully I'll find the time to write a blog post about TimeGraphic one day, it's actually a nice piece of algebra.

Bidirectional controls

Well, an infinitesimal delay alone is not enough; the feedback loop would just be stretched out in time. You have to disable event updates at some point.

I think a good litmus test for the new Behavior implementation is the following example: two text boxes like in CurrencyConverter, each text box sends updates whenever the text is changed, be it programmatically or by the user. To prevent the loop, the idea to disable updates (that's the litmus test) on the text box that has the focus, i.e. that the user is editing. This doesn't require infinitesimal delays, I think.

The problem with infitesimal delays is that I don't have a model implementation for them. :-(

Where to get updates from?

Sounds worthwhile indeed. But it should probably be baked into the wxHaskell bindings, i.e. without any reference to reactive-banana.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Incremental updates

Since there's no obvious way to solve the incremental updates problem right now, I would suggest we focus on simply giving Behavior update information; the model shouldn't change at all, the framework API changes should be fairly minimal, and since the structure is closer to an incremental update model, it'll help transitioning to one in the future.

So, DatabaseTime and TimeGraphic would stay the way they are (although I'd suggest refactoring DatabaseTime to data DatabaseTime = DatabaseTime { valueDB :: Behavior (Database a), changesDB :: Event (CUD DatabaseKey a) } since these changes should allow observing the initial value of a Behavior in NetworkDescription anyway).

Bidirectional controls

Hmm, I'm not convinced reactive-banana would need special support for this. What you need is to be able to "stop listening" to the text box when it's focused, and simply hold the previous value it had. If you can't implement this now, I expect you'd be able to with dynamic Behavior switching.

Where to get updates from?

Ideally, but there are so many widgets that simply making use of Reactive.Banana.WX.behavior a little more complicated is likely to be more practical in the short term, IMO.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

After thinking for a while, I believe I have a solution that doesn't break compatibility at all. There are three proposals.

Proposal 1

API changes

Add the following:

fromDiscrete :: IO a -> Event () -> NetworkDescription (Behavior a)
initial :: Behavior a -> NetworkDescription a
sample :: Behavior a -> NetworkDescription (Event ())

Explanation

The idea is that ordinary fromPoll Behaviors still work in a polling manner, but fromDiscrete constructs the equivalent of a Discrete. Combining Behaviors (e.g. with (<*>)) produces update events as follows, where Poll and Discrete u represent a polling Behavior and a discrete Behavior with update event u respectively:

Poll       • Poll       = Poll
Poll       • Discrete u = Discrete u
Discrete u • Discrete v = Discrete (unionWith const u v)

initial returns the initial value of a Behavior.

sample returns the update event of a Behavior; for a polling Behavior, it returns the equivalent of your networkUpdate. This should be the right thing to do in basically every circumstance; the network can only "react" to an update, so although obviously sampling the updates something like an RNG doesn't make sense, it does the most reasonable thing for polling Behaviors.

Pure Behaviors should have reasonable update events too, e.g.:

sample (accumB x e) ≡ return (void e)
sample (stepper x e) ≡ return (void e)

but I think it would work fine if networkUpdate was used in these cases, too. The definitions make me slightly uneasy; since these accumulations update "slightly after" e, would these update events result in holding back on reporting on the new value of the Behavior until the next occurrence of e? Is this problematic?

Advantages

This doesn't break backwards compatibility at all, and allows pure-polling Behaviors to efficiently coexist with discrete ones; if you have fromPoll reallyExpensiveComputation, then that computation is only executed when sampled by an Event. You don't have to choose the update event up-front for something like that. At the same time, it allows bundling an efficient update event into any Behavior.

Disadvantages

The combination of update events shows a possible problem: combining a polling and a discrete event always produces a discrete event. This means that if you combine your expensive polling Behavior with a discrete one, it ends up getting computed all the time. This is disastrous if you only care about the result of the combined event on a rare event, but the discrete Behavior updates all the time.

However, the intention is that all Behaviors are computed in a polling manner, and the only use of the update event is to expose it with sample. So this problem only occurs if you sample something that directly depends on such a combined Behavior, and if you made the combination of a polling and discrete Behavior a polling Behavior, then I think that same sample call would return the networkUpdate-equivalent. So this probably isn't a big problem.

Proposal 2

API changes

We decouple the update bundling from the Behavior creation:

withUpdate :: Event () -> Behavior a -> Behavior a
initial :: Behavior a -> NetworkDescription a
sample :: Behavior a -> NetworkDescription (Event ())

fromDiscrete can be implemented in terms of this:

fromDiscrete :: IO a -> Event () -> NetworkDescription (Behavior a)
fromDiscrete m u = withUpdate u <$> fromPoll m

Advantages

This is more elegant.

reactive-banana-wx could keep its behavior definition, and you could specify an update event separately:

text <- withUpdate u <$> behavior input text

This also lets you work around the "polling + discrete = discrete" problem (if it really is a problem); just specify the sampling event you actually use:

let sampledOnButtonClick = withUpdate buttonClicked (updatedOften <*> expensive)

Disadvantages

I think this might be more difficult to implement, though I'm not sure how.

Proposal 3

API changes

We don't provide withUpdate at all:

initial :: Behavior a -> NetworkDescription a
sample :: Behavior a -> NetworkDescription (Event ())

Explanation

If the pure Behavior creation functions use the specified Events as their update event, then we can implement withUpdate easily:

withUpdate :: Event () -> Behavior a -> Behavior a
withUpdate u b = do
  x0 <- initial b
  return $ stepper x0 (b <@ u)

Advantages

Strictly simpler than proposal 2 :)

Disadvantages

It relies on pure Behaviors using their generating Events as their update events, which might not be practical.

I'm not sure if the fact that stepper updates "slightly after" the Event causes problems here.

Summary

I think proposal 2 should be just as feasible as proposal 1, and it's a lot nicer. If it works, proposal 3 is nicer still.

While these can be implemented as an additional semantics as in issue #26, the fact that they don't add anything to the model (just to the implementation, in NetworkDescription), and don't break backwards compatibility at all, mean that it's probably simplest to implement this directly.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Correction: Proposal 3 is wrong; withUpdate would have to have the type:

withUpdate :: Event () -> Behavior a -> NetworkDescription (Behavior a)

since it uses initial. Accordingly, I now favour proposal 2.

Another thing that might be useful is a way to observe the update events in "pure" FRP code in a safe manner, to be used when constructing other update events. That is, it's useful to be able to say "this Behavior's update event is the union of an event and another Behavior's update event". withUpdate is a lot simpler, and so I'd propose just starting with that for now, but I can imagine something like:

-- Update is a monad (although I think Applicative would be sufficient)
updates :: Behavior a -> Update (Event ())
withUpdate :: Update (Event ()) -> Behavior a -> Behavior a

e.g.

b3 = withUpdate (union <$> updates b1 <*> pure e) b2

But it's probably best to stick with the simpler proposal 2, at least to start with.

(That b3 example makes me wonder if withUpdates mightn't be a better name. Not very important, of course...)

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

My work on reative-banana-0.5 is progressing forward and it's time to revisit this issue.

Proposal

It turns out that the following version of fromDiscrete is very easy to implement

fromDiscrete :: IO a -> AddHandler () -> NetworkDescription t (Behavior t a)

because it doesn't need any special support from the internal implementation. This is a very good sign. In fact, the implementation is simply

fromDiscrete poll addHandler = do
    let addHandler' h = addHandler $ \() -> poll >>= h
    eupdate <- fromAddHandler $ addHandler'
    initial <- poll
    let bresult = stepper initial eupdate
    return bresult

In other words, whenever the udpate event happens, we simply poll the IO action and create a behavior from the new event. That's possible because we are allowed to perform IO actions inside an AddHandler. Of course, we dont' have the additional flexibility of an Event, but I think that's ok.

(Some care should be taken about the initial value, but that is not important here.)

Problems

The only problem with this and all the other approaches is that the resulting Behavior always "lags behind", due to the use of stepper. In other words, bresult <@ eupdate yields the previous value of the behavior, not the value that it is currently updated with.

I'm not sure whether this is good or bad. It won't be a problem when output behaviors are built without sampling directly from the input behaviors via the Applicative instance. Also, it is consistent with the creation of internal behaviors or Discrete via stepper, which I would label as "good". However, sampling the behavior with its update events may give surprising results.

Moving forward

Since the new behavior creation is easy to implement, I will simply try that. The examples will tell me whether the mentioned problem is relevant in practice or not.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

I believe your fromDiscrete is essentially the withUpdate u <$> fromPoll m implementation I gave in my previous comments, combined with my fromDiscrete implementation in terms of stepper. I don't think there's any need to restrict it to IO a rather than Behavior a, and if a Behavior version can be implemented, then it seems to me that withUpdate :: Event () -> Behavior a -> Behavior a should be pretty simple too, resulting in my preferred second proposal. But maybe there's implementation issues I'm not aware of.

Still, I don't quite see how adding fromDiscrete solves the issue. It's the input side of things, but as far as I can tell, it doesn't do much without initial and sample.

It's nice to see this issue moving forwards :)

from reactive-banana.

HeinrichApfelmus avatar HeinrichApfelmus commented on September 26, 2024

Ok, I have implemented something as mentioned. The function is called fromChanges.

Thanks a lot for bringing this up, Elliott, the update tracking inside Behavior does simplify a lot of code! The previous Discrete type did not turn out to be a good idea.

That said, it is no panacea: the CRUD example is still very difficult to write and still does not quite work as intended. I have an idea how to rectify that, though, which I will detail in a blog post soon.

For now, I'd like to call it a day and release reactive-banana-0.5.

from reactive-banana.

ehird avatar ehird commented on September 26, 2024

Ah, now that I read the code, I see that you've implemented exactly my proposal 3, and that withUpdate isn't actually necessary, because you can just use (<@).

I'm very happy with this change. Of course, it'd be great if we could have one single type that handles all incremental updates elegantly, but that seems like a very difficult problem to solve, and this is already much better than the previous situation.

Thanks a lot for this; I really like where reactive-banana is going! :)

from reactive-banana.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.