HeinrichApfelmus / reactive-banana

Library for functional reactive programming in Haskell.
https://wiki.haskell.org/Reactive-banana
521 stars 71 forks source link

switcher function (switcher :: Behavior (Behavior a) -> Behavior a) #121

Open archaephyrryx opened 8 years ago

archaephyrryx commented 8 years ago

Hello,

I have been working with your FRP libraries in Haskell (initially threepenny, but I am simultaneously porting some of the widgets I created into the Reactive-Banana-WX paradigm), and I am the kind of person who tends to overthink things and do library-building for utility types, typeclasses, and functions even if they will ultimately go nowhere in a later version. In any case, I was wondering if it was possible to create a switcher function, of type Behavior (Behavior a) -> Behavior a, which would semantically be switcher bb = (bb time) $ time. I would attempt to implement such a function myself, but I don't have sufficient understanding of the library's internal structure to know how to do so in the spirit of reactive-banana. Could you include such a function, or propose an implementation that I could use in my own libraries?

ocharles commented 8 years ago

I believe this would be akin to having an instance Monad Behaviour - r-b doesn't provide this, and if you search Github issues you should be able to find a longer discussion around why it is very difficult.

On Sun, 27 Dec 2015 2:35 am Peter Duchovni notifications@github.com wrote:

Hello,

I have been working with your FRP libraries in Haskell (initially threepenny, but I am simultaneously porting some of the widgets I created into the Reactive-Banana-WX paradigm), and I am the kind of person who tends to overthink things and do library-building for utility types, typeclasses, and functions even if they will ultimately go nowhere in a later version In any case, I was wondering if it was possible to create a switcher function, of type Behavior (Behavior a) -> Behavior a, which would semantically be switcher bb = (bb time) $ time I would attempt to implement such a function myself, but I don't have sufficient understanding of the library's internal structure to know how to do so in the spirit of reactive-banana Could you include such a function, or propose an implementation that I could use in my own libraries?

— Reply to this email directly or view it on GitHub https://github.com/HeinrichApfelmus/reactive-banana/issues/121.

atzeus commented 8 years ago

I cannot find the discussion, can you link it?

ocharles commented 8 years ago

https://github.com/HeinrichApfelmus/reactive-banana/issues/101 is what I was thinking of

On Sun, 27 Dec 2015 2:23 pm atzeus notifications@github.com wrote:

I cannot find the discussion, can you link it?

— Reply to this email directly or view it on GitHub https://github.com/HeinrichApfelmus/reactive-banana/issues/121#issuecomment-167417707 .

archaephyrryx commented 8 years ago

I would also be satisfied by something of the type Behavior (Behavior a) -> Moment (Behavior a), as many of the Behavior/Event manipulation I am dealing with happens inside of a MomentMonad context.

jdreaver commented 8 years ago

Hey @archaephyrryx, here is something I use similar to what you want:

sampledBehavior :: Event () -> Behavior (Behavior a) -> Moment (Behavior a)
sampledBehavior e b =
  do valNow <- valueB b >>= valueB
     let e' = switchE (((<@ e) <$> b) <@ e)
     stepper valNow e'

In this example, think of the Event () as a "syncing event." More specifically, the output Behavior is given the "correct" value whenever the syncing event fires. I am using FRP in a scene graph system, where nodes in the graph are either drawable primitives, or transformations of collections of primitives. I represent the mutable parts of the graph with Behaviors. In this system, my Event () is the event that indicates I am about to render the scene in OpenGL. (Here is a link to this function in my "experiments" file, where I try to sort out how to handle trees of Behaviors.)

A more exciting example is this: if you have access to a Behavior and the Event that corresponds directly to the steps in that Behavior, then you can get something very close to what you want. You get this situation when you create a behavior with stepper; the Event used to create the Behavior can be paired with it. In the following example, I have a data type called Observable, which stores these Event/Behavior pairs.

data Observable a = Observable (Behavior a) (Event a)

joinObs :: Observable (Observable a) -> Moment (Observable a)
joinObs (Observable oB oE) =
  do let e = switchE $ ((\(Observable b e') -> b <@ (oE `union` e')) <$> oB) <@ oE
     valNow <- valueB oB >>= (\(Observable b _) -> valueB b)
     b <- stepper valNow e
     return $ Observable b e

union :: Event a -> Event b -> Event ()
union e1 e2 = unionWith (\_ _ -> ()) (void e1) (void e2)

As you can see, when we use the Observable abstraction, we get almost exactly what you want.

I know these examples aren't perfect, but I see them as a couple of pragmatic alternatives to a monadic join on Behaviors. I'm always looking for better ways to solve the problem more efficiently without requiring a Monad instance for Behavior. Also, I haven't debugged these two functions, so I would test them out to make sure they work. They do type-check though! :)

jdreaver commented 8 years ago

Also, if anyone else has (partial?) solutions to this problem that don't involve a Monad instance, I would love to see them. We could add them to a wiki somewhere.

(As a side-note, I feel like I've either create or reinvented a lot of FRP design patterns over the past few months. By that I mean I have tried to figure out how to structure large applications, create model-view separation, use trees of nested Behaviors, etc. I feel like a central wiki or even just a Markdown file in a Github repo would be a cool place to collect a lot of advanced or real-world FRP techniques, so new users don't have to reinvent the wheel.)

HeinrichApfelmus commented 8 years ago

@archaephyrryx As @ocharles explains, this is equivalent to a Monad instance for Behaviors. In principle, this is possible, but in practice, this has implications for performance.

if you have a concrete example in mind where this combinator is particularly useful, I'm happy to consider this or related combinators for inclusion. My personal experience is that most instances where a (>>=) for Behaviors sounds like a good idea are better served by the Moment monad.

I feel like a central wiki or even just a Markdown file in a Github repo would be a cool place to collect a lot of advanced or real-world FRP techniques, so new users don't have to reinvent the wheel.

@jdreaver I think that's an excellent idea! I have created a new repository: https://github.com/HeinrichApfelmus/frp-guides . I intend to add the widget design guide shortly.

greyson commented 6 years ago

I know I'm late to the party; but I'm also looking for Behavior (Behavior a) -> Behavior a (or Behavior (Behavior a) -> Moment (Behavior a);

I'm trying to take a Behavior (Map k (Behavior v)) and combine it with another Event k elsewhere in the application to obtain the proper Behavior v to avoid a CPU stampede as many other Behaviors in the application will be interested in one or two k values at a time.

mitchellwrosen commented 6 years ago

@greyson This is possible with the current API assuming you have some Behavior v to use before any Event k fires:

bMap :: Behavior (Map K (Behavior V))

eKey :: Event V

fmap over bMap to partially apply map lookup:

bFoo :: Behavior (K -> Maybe (Behavior V))
bFoo =
  (\m k -> Map.lookup k m) <$> bMap

Create a new event that samples this behavior whenever eKey fires:

eFoo :: Event (Maybe (Behavior V))
eFoo =
  bFoo <@> eKey

Filter out Ks that weren't in the map, so there's no corresponding Behavior V:

eBar :: Event (Behavior V)
eBar =
  filterE eFoo

Create a new event that dynamically switches to the latest Behavior V emitted by eBar, beginning with some behavior b0:

eBaz :: MonadMoment m => m (Behavior V)
eBaz =
  switchB b0 eBar
greyson commented 6 years ago

I should not have used the Event k as an example -- Not only can the Event k be very far distant from this table (in my application) but more often, it is better modeled as a Behavior. There are some places in the application which will want the V based on an Event k, and some that will want it based on a Behavior k.

For example:

type Market = HashMap Symbol (Behavior Price)

marketFromTrades :: Event Trade -> Moment (Behavior Market)
marketFromTrades trades = uncurry HM.insert <$> newTradeSymbols trades

newTradeSymbols :: Event Trade -> Moment (Event (Symbol, Behavior Trade))
newTradeSymbols trades = mdo
  let result = filterJust $ observeE $ newTradeOnly trades <$> foundSymbols <@> trades
  foundSymbols <- accumB Set.empty (Set.insert . fst <$> result)
  return result

newTradeOnly :: Event Trade -> Set Symbol -> Trade -> Moment (Maybe (Symbol, Behavior Trade))
newTradeOnly trades found t = let sym = tradeSymbol t in
  if pair `Set.member` found
  then return Nothing
  else
    stepper t (filterE ((pair ==) . tradeSymbol) trades) >>= \b ->
    return $ Just (pair, b)

I would like to have this function work (which comes from Sodium/Java):

switchC :: MonadMoment m => Behavior (Behavior a) -> m (Behavior a)

marketTradePrice :: Behavior Market -> Symbol -> Moment (Behavior (Maybe Trade))
marketTradePrice market sym =
    switchC $ maybe (pure Nothing) (fmap Just) . HM.lookup sym <$> market

This allows for safer and more flexible usage: Dynamic consumers of multiple symbol prices can simply lift all the prices when they are created, rather than having to know ahead of time which of the newSymbol events creating them most recently happened.

I was surprised not to find the Sodium semantic of switchS (switchE :: Behavior (Event a) -> m (Event a)) and switchC (switchB :: Behavior (Behavior a) -> m (Behavior a)) since the switchE and switchB of RB is much more restricted in its flexibility. To get the current semantic back would only be from switchB init changes to switchB =<< stepper init changes and from switchE changes to switchE =<< stepper never changes.

It seems that Sodium's model is much more flexible; and I know that without it, a number of the abstractions in my (10k lines of) Sodium/Java will not translate to Reactive Banana.

mitchellwrosen commented 6 years ago

I'm sorry I don't totally understand your example, but it's possible you can benefit from simply keeping a Behavior and the Event that steps it forward together in the same data type.

data Dynamic a = Dynamic 
  { current :: Behavior a
  , updates :: Event a
  }

This should allow you to avoid changes (which is a bit of a back door), and make functions roughly equivalent to switchS/switchC, but for a pushed-based implementation.

HeinrichApfelmus commented 6 years ago

@greyson My main trouble with switchB is that it pretty much gives you a monad instance, but is too expensive for that.

The Moment type is very similar to Behavior, but does have a monad instance (at the price of no notification of changes.) What happens if you use

type Market = HashMap Symbol (Moment Price)

? Is that feasible?