concur icon indicating copy to clipboard operation
concur copied to clipboard

Resuming widgets

Open pkamenarsky opened this issue 5 years ago • 13 comments

Imagine the following scenario:

counter x = do
  _ <- div [ onClick ]
    [ text $ T.pack (show x)
    ]

  counter (x + 1)

other :: T.Text -> Widget HTML T.Text
other str = do
  e <- div []
    [ input [ onInput, value str ]
    , text str
    ]

  pure $ targetValue $ target e

container str = do
  newStr <- div [] [ counter 0, other str ]
  container newStr

I.e. a composition of both neverending and non-recursive widgets. The problem is that every time other finishes, counter is going to lose its state.

To fix this, we could "ban" recursion (and thus neverending widgets) and explicitly thread arguments between parent and children components, essentially emulating Elm, but in a somewhat free-form way. However, disallowing recursion isn't even the worst thing; to fix state loss, instead of writing a widget like this:

workflow = do
   a <- step1
   b <- step2 a
   ...
   pure b

one would have to turn the above into a state machine:

workflow = do
  st <- get
  case st of
    Step1 -> do
      a <- step1
      put (Step2 a)
    Step2 a -> do
      b <- step2 a
      put (Result b)

To me, reifying time flow is the selling proposition of Concur and something no other UI paradigm offers, to my knowledge. Going back to explicit state machines in the spirit of React or Elm doesn't make much sense.

I've thought a bit about this but the solution I've come up with feels a bit off. Basically, we'd change the type of orr to:

orr :: [Widget v a] -> Widget v (a, [Maybe (Widget v a)]) -- specialised to Widget

I.e. orr returns both the value of the ending Widget, as well as all the continuations of the remaining Widgets at that point. With this, we could rewrite the first example to:

resume = flip fromMaybe

container str c = do
  (newStr, [c, _]) <- div [] [ resume c $ counter 0, other str ]
  container newStr c

But this does not seem ideal. It would be nice if we didn't have to modify orr for this, but then there would be no way to get hold of the continuations of the non-firing Widgets. I think it should be possible to write something like this:

reify :: Widget v a -> Widget v (a, [Maybe Widget v a])

which would return the result along with all the continuations of a Widget's children, but being able to break the encapsulation of the otherwise fully opaque Widget type that easily is probably a bad idea.

I've also thought about crazy stuff like actually calling all continuations after a Widget ends, effectively running the world in parallel and introducing a join combinator - which somehow collects the results from the different "parallel universes" - but that seems like it would be awfully inefficient and probably not even possible. Sounds cool though.

Maybe I'm overlooking something fairly obvious. I saw the Gen stuff in the Purescript repo and thought about making each Widget a pipe-like thing along with yield and await operators, so that outside state can be "pushed" into neverending widgets, but this wouldn't help if widgets can still finish and thus force their siblings to lose state.

I've also had the idea of ditching the Monad constraint altogether and making Widget a selective Applicative, which still allows for some control flow but is fully introspectable. This would bring the benefit of being able to collect every UI transition upfront (and maybe even precompute DOM diffs) but more importantly, of allowing us to attach the continuations directly to the Widget VDOM node (which would never change).

However, although SelectiveDo might be implemented someday, until it isn't it's fairly cumbersome to program with selective Applicatives. So that's off the table, at least for now.

Do you have any thoughts on this?

pkamenarsky avatar Jul 03 '19 09:07 pkamenarsky

Interesting! It's very illuminating to see concur's core mechanic from other people's perspectives, and to hear fresh ideas.

I.e. a composition of both neverending and non-recursive widgets. The problem is that every time other finishes, counter is going to lose its state.

Well that's by design. If you are composing other and counter with <|>, you are saying that either of them could finish and you don't care. Semantically once you get a return value, it could have come from any of them.

From a language consistency perspective - Since we are in a monad and continuations are hidden behind a lambda, it's not possible to say how any change in state would affect the child widgets, i.e. it's going to be very hard to maintain the state of the child in any meaningful form. For example, if the parent renders the counter for some states and does not render it for some states, then do what does it mean to maintain the count across those parent state changes?

Applicative functors (selective or otherwise) are not appropriate because they don't allow plumbing the output of a previous widgets into a subsequent widget. Adding selectivity just allows us to write the equivalent of if condition then someWidget else anotherWidget, which while a great step, doesn't go far enough. For example, you can't still do something as simple as -

do
  x <- someWidget
  y <- anotherWidget x
  ...

One quick solution, that I just thought of while composing this reply, is creating some sort of an applicative-ish combinator which nests things while semantically treating them as siblings, so updates to one do not affect the other.

Imagine two combinators like this -

<|$> :: Widget HTML a -> (Widget HTML a -> Widget HTML b) -> Widget HTML b
<$|> :: (Widget HTML a -> Widget HTML b) -> Widget HTML a -> Widget HTML b

Both of them compose Widget a and Widget b together like <|>, but in the UI Widget a is shown nested inside Widget b.

So then we could write the counter example as -

counter :: forall a. Widget HTML a
counter x = do
  _ <- div [ onClick ]
    [ text $ T.pack (show x)
    ]
  counter (x + 1)

other :: T.Text -> Widget HTML T.Text
other str = do
  e <- div []
    [ input [ onInput, value str ]
    , text str
    ]
  pure $ targetValue $ target e

container str = counter 0 <|$> counterContainer
  where
    counterContainer counterUI = do
      newStr <- div [] $ [ counterUI, other str ]
      counterContainer newStr

Both these combinators can be easily written in a similar manner as the existing remoteWidget combinators (Purescript, or Haskell).

I'll try to add these soon and check if it works.

ajnsit avatar Jul 04 '19 00:07 ajnsit

I ended up pursuing a different direction, especially in the context of Replica. The problem really is just about how to best share state in the context of neverending widgets.

So, having a Δ a type of "changeable/reactive values" (which is just a wrapper around a (TVar a, TChan a) tuple), we introduce two combinators, local, which creates a Δ a with an initial value, and with, which listens to changes to a Δ a and allows for modification:

local :: a -> (Δ a -> Widget HTML b) -> Widget HTML b
with :: Δ a -> (a -> Widget HTML (Either a r)) -> Widget HTML r

For example, to implement two counters sharing the same state, we could do:

counter :: Int -> Widget HTML (Either Int r)
counter x = do
  div [ onClick ] [ text (T.pack $ show x) ]
  pure $ Left (x + 1)

counters = local 0 $ \x -> div []
  [ with x counter
  , with x counter
  ]

The cool thing is that this allows for super easy state sharing among multiple Replica connections for basically free (i.e. open an app in two tabs and watch modifications in one tab being reflected in the other).

The main drawback is that Δ can't be made a Functor/Applicative because with needs access to the TVar/TChan in the original Δ. This means that we'd have to provide several combinators like with2, with3 and so on in order to allow for (transactional) updates of multiple Δs at once.

However, combinators like e.g. mapValue and pairValues might turn out to be enough:

mapValue :: Lens s t -> Δ t -> Δ s
pairValues :: Δ a -> Δ b -> Δ (a, b)

Note: with could also be encoded in the following manner, but I think I'm slightly in favor of the more explicit Either variant, mainly because the type signatures are simpler:

with :: Δ a -> ((a -> Widget HTML r) -> a -> Widget HTML r) -> Widget HTML r

What do you think? From what I understand you've already written bigger apps in Concur, so I'm really interested in hearing about what patterns work in your opinion.

EDIT: Also, this kind of ties into your Signals idea in the Purescript branch, although it's not quite the same. Maybe the two approaches could be combined somehow?

pkamenarsky avatar Jul 28 '19 10:07 pkamenarsky

I don't understand how this solves the local state problem. In the Counter example, the (shared) state for both the counters is explicitly managed "above" the counter level, which is already easy in Concur. For example, it's trivial to write something like loopState (https://github.com/ajnsit/purescript-concur/blob/master/lib/src/Concur/Core/Patterns.purs#L15) and then use it -

counter :: Int -> Widget HTML (Either Int r)
counter x = do
  div [ onClick ] [ text (T.pack $ show x) ]
  pure $ Left (x + 1)

counters = loopState 0 \x -> div []
  [ counter x
  , counter x
  ]

Can you give an example of using loop and with to do something that can't be done by loopState?

ajnsit avatar Jul 30 '19 16:07 ajnsit

Can you give an example of using loop and with to do something that can't be done by loopState?

For example:

counter :: Int -> Widget HTML (Either Int ())
counter x = do
  div [ onClick ] [ text (T.pack $ show x) ]
  if x < 10
    then pure $ Left (x + 1)
    else pure $ Right ()

counterWithMessage x = do
  with x counter
  div [] [ text "Counter finished" ]

countersWithMessage = local 0 $ \x -> div []
  [ counterWithMessage x
  , counterWithMessage x
  ]

Afaics that would be impossible with loopState, since counterWithMessage can't return the updated counter state.

EDIT: i.e. imagine sharing some state between two completely unrelated components, each with their own steps, consisting of long-running or neverending widgets.

pkamenarsky avatar Jul 30 '19 16:07 pkamenarsky

Okay I see what you mean. The API looks very clean, but IMO semantically the API is a tad more magical than it should be.

Specifically, the API controls both the input and output of the widget, but passing state "down" into a widget is not a problem with Concur.

Also, if I understand the semantics correctly, as soon as an intermediate state value is emitted via Left (x+1), everything inside local would rerender, which means values would flow from top down anyways. However the current API makes it seem like it has FRPish semantics which is misleading.

What do you think of the following API instead -

with :: forall a void. ∆ a -> a -> Widget HTML void
local :: forall a v r. a -> (∆ a -> Widget v r) -> Widget v r

Δ is probably the wrong letter here. It's more like a simple channel, just a way to signal values "Up" the scope chain. For example, as you suggested, it could just be a TChan. Then it would also be a Contravariant Functor. (BTW Your Δ is likely a constrained Profunctor with both type args constrained to be same).

With this API we can write your example like below. I think it makes the data flow more explicit.

counter :: ∆ Int -> Int -> Widget HTML Unit
counter k x = do
  void $ D.div [ P.onClick ] [ D.text $ show x ]
  if x < 10
    then with k $ x + 1
    else pure unit

counterWithMessage :: forall a. ∆ Int -> Int -> Widget HTML a
counterWithMessage k init = do
  counter k init
  D.div [] [ D.text "Counter finished" ]

countersWithMessage :: forall a. Widget HTML a
countersWithMessage = local 0 \k -> D.div []
  [ counterWithMessage k 0
  , counterWithMessage k 0
  ]

ajnsit avatar Jul 30 '19 20:07 ajnsit

FYI - I added a simple implementation for with and local (probably need renaming) to purescript-concur. An example here - https://github.com/ajnsit/purescript-concur/blob/master/examples/src/Test/Wire.purs. What do you think?

ajnsit avatar Jul 30 '19 21:07 ajnsit

@pkamenarsky On thinking about this more I have warmed up to the API you suggested, except for the implicit wiring with Either at the last stage. I would much rather pass an explicit Wire all the way down. I updated the Purescript example to use this new API, and to also test sub states with Lens mapping. I think this is a pretty good API on top of Widget, so thanks for suggesting it!

counter :: Wire (Widget HTML) Int -> Widget HTML Unit
counter wire = do
  let x = wire.value
  void $ D.button [ P.onClick ] [ D.text $ show x ]
  if x < 10
    then wire.send $ x + 1
    else pure unit

counterWithMessage :: forall a. Wire (Widget HTML) Int -> Widget HTML a
counterWithMessage wire = do
  counter wire
  D.div [] [ D.text "Counter finished" ]

wireWidget :: forall a. Widget HTML a
wireWidget = local (Tuple 0 0) \wire -> D.div []
  [ D.div' [D.text "This counter is independent of the other two "]
  , counterWithMessage (mapWire L.first wire)
  , D.div' [D.text "These two counters have the same state"]
  , counterWithMessage (mapWire L.second wire)
  , counterWithMessage (mapWire L.second wire)
  ]

ajnsit avatar Jul 31 '19 08:07 ajnsit

Ah, that's clever! However, I'm proposing something subtly different - with doesn't rerender everything in local, so we could do something like this:

counter :: Text -> Int -> Int -> Widget HTML (Either Int ())
counter message to x = do
  div [ onClick ] [ text (message <> T.pack (show x)) ]
  if x < to
    then pure $ Left (x + 1)
    else pure $ Right ()

counterWithMessage x = do
  with x (counter "Counter 1" 10)
  div [ onClick ] [ text "Counter 1 finished" ]
  with x (counter "Counter 2" 20)
  div [ onClick ] [ text "Counter 2 finished" ]

countersWithMessage = local 0 $ \x -> div []
  [ counterWithMessage x
  , counterWithMessage x
  ]

The general goal is to be able to easily compose long-running or neverending widgets with shared state. loopState expects that nothing will ever happen after a stateful widget, and your proposed local/with/Wire combinators expect that nothing will happen before, if I'm understanding correctly. What I'm proposing allows for recursive widgets everywhere. FWIW, here's the Haskell implementation of local/with, maybe this will help clarify things:

data Δ a = Value (TVar a) (TChan a) deriving Eq

local :: a -> (Δ a -> Widget HTML b) -> Widget HTML b
local a f = do
  v <- liftUnsafeBlockingIO
    $ atomically
    $ liftA2 Value (newTVar a) newBroadcastTChan
  f v

with :: Δ a -> (a -> Widget HTML (Either a r)) -> Widget HTML r
with (Value ref bcast) w = do
  (a, read) <- liftUnsafeBlockingIO
    $ atomically
    $ liftA2 (,) (readTVar ref) (dupTChan bcast)
  go read a
  where
    go read a = do
      r <- fmap Left (w a) <|> fmap Right (get read)
      case r of
        Right a' -> go read a'
        Left (Left a') -> do
          write read a'
          go read a'
        Left (Right b) -> pure b

    get read = liftSafeBlockingIO $ atomically $ readTChan read

    write read a = liftUnsafeBlockingIO $ atomically $ do
      writeTVar ref a
      writeTChan bcast a
      readTChan read  -- don't react to the value we just wrote

EDIT: I think your with is more akin to put below:

put :: Δ a -> a -> Widget HTML ()
put (Value ref bcast) a = liftUnsafeBlockingIO $ atomically $ do
  writeTVar ref a
  writeTChan bcast a

However, I'm hesitant to include this in the API, since it would encourage a more "stateful" style of programming, and I think with is general enough.

pkamenarsky avatar Jul 31 '19 11:07 pkamenarsky

Quick experience report: I've been doing Concur (well concur-replica) programming for about a month now, and the scenario described in this issue was becoming a very serious problem.

If I hadn't seen this issue I wouldn't have known what to do-- happily I was able to copy the local and with implementations. They've worked well so far.

For the sake of new users and Concur adoption, should we consider moving them or some alternative solution into the library?

seagreen avatar Jan 26 '20 00:01 seagreen

A few more thoughts:

Making sure I understand the problem

One of the most enjoyable things about Concur to me is having local state at the leaves. Imagine in a strategy game, you've got things like open help tooltips, partially filled out forms (for things like setting what a base is producing), all that kind of stuff.

When doing this style of programming nothing above the leaf level can ever recurse on itself. If it does it will wipe out the local state of all its children.

So I think getting sharing of values like this right is going to be very important.

The current solutions

Imagine you're making a level editor for a game. You want a form that can be displayed permanently on the screen for making new unit types. It has a "Submit" button to make a new unit type. When that's hit you want to communicate it to the rest of the UI, but you also want to leave the state of the form alone, on the guess that the settings like speed, firepower, etc might be similar for the next unit they create, and they will only want to tweak them instead of starting from scratch.

Currently with concur-core the only way to get values out of a widget is to return them, so you're basically forced into TEA: InternalState -> Widget html (Either InternalState NewUnitType). If you don't report the InternalState to your parent, it won't have it on hand to re-initialize you once you return a NewUnitType.

The Δ strategy is definitely an improvement on this. You can make its type Δ NewUnitType -> Widget html a.

However, this isn't as descriptive as we could be, because gives the widget the power to use the Δ for both reading and writing, but we only want to use it for writing.

An idea

What about parameterizing Widget itself? We could have a WidgetStream html read write return and then do type Widget html a = WidgetStream html Void Void a.

Then, for this example, the type of the unit designer would be WidgetStream html Void NewUnitType a.

This might be a horrible idea, but I thought I'd throw it out there in case it's interesting.

seagreen avatar Jan 26 '20 18:01 seagreen

I kinda agree with @ajnsit here in that concur-core should probably not provide functions and combinators for managing state in specific ways, I think it should only concern itself with widget composition (and their timelines). I believe it's possible to have a much nicer API for this problem which doesn't involve talking about state — one of the strongest core ideas or consequences of the concur model.

This idea essentially uses these core combinators:

-- | Fork the given 'Widget', allowing it to run in parallel with any other 'Widget'
-- while keeping its internal timeline/state closure. Widgets forked with this function
-- can be joined back again in another timeline with the 'join' function.
-- For external observers, a forked 'Widget' never finishes until it is joined with 'join'.
fork :: Widget ui a -> IO (Widget ui (Forked a))

-- | Erase the return type of a forked 'Widget', preventing it from being joined back in a timeline. 
forget :: Widget ui (Forked a) -> Widget ui void

-- | Join a forked widget (i.e. a 'Widget' whose return type is @'Forked' a@) in the
-- current timeline, allowing waiting for its termination and inspecting its return value.
join :: Widget ui (Forked a) -> Widget ui a

So for the problem described we could have:

counter :: Int -> Widget HTML void
other :: Text -> Widget HTML Text
loop :: a -> (a -> Widget ui a) -> Widget ui void

container :: Text -> Widget HTML void
container str0 = do
  forkedCounter <- liftIO $ fork $ counter 0
  loop str0 \str ->
    div [] [ forget forkedCounter, other str ]

Which, as a diagram is something like this (sorry for the sloppy drawing): diagram

If we wanted container to ever finish and expect counter to also finish at some point we could just join it back again in the timeline, i.e.:

countUntil100 :: Int -> Widget HTML Int
someComponentThatTakesALongTimeToFinish :: Text -> Widget HTML Text

container :: Text -> Widget HTML Int
container str = do
  forkedCounter <- liftIO $ fork $ countUntil100 0
  newStr <- div [] [ forget forkedCounter, someComponentThatTakesALongTimeToFinish str ]
  oneHundred <- join forkedCounter
  ...

Something like purescript-fork would be pretty useful.

Please let me know what you @ajnsit and @pkamenarsky think of this.

arthurxavierx avatar Jul 10 '21 12:07 arthurxavierx

@arthurxavierx that's an interesting model! Though I'm not sure I understand the semantics. For example, this piece of code -

  newStr <- div [] [ forget forkedCounter, someComponentThatTakesALongTimeToFinish str ]
  oneHundred <- join forkedCounter

The join forkedCounter will not be executed until someComponentThatTakesALongTimeToFinish returns a value. When in reality we want the counter to be able to end before the long running component.

ajnsit avatar Jul 14 '21 13:07 ajnsit

The join forkedCounter will not be executed until someComponentThatTakesALongTimeToFinish returns a value. When in reality we want the counter to be able to end before the long running component.

@ajnsit I'd thought that, just as in the fork/join concurrency model, the counter would be able to end before join is applied to it, but we're only able to access its return value with join.

If we want to race both processes such that the counter can end before the long running component, then the best approach would be just not forking any widget, right?

countUntil100 :: Int -> Widget HTML Int
someComponentThatTakesALongTimeToFinish :: Text -> Widget HTML Text

container :: Text -> Widget HTML Int
container str = do
  result <- div [] [ Left <$> countUntill100, Right <$> someComponentThatTakesALongTimeToFinish str ]
  case result of
    ...

arthurxavierx avatar Jul 14 '21 14:07 arthurxavierx