turion / rhine

Haskell Functional Reactive Programming framework with type-level clocks
http://hackage.haskell.org/package/rhine
118 stars 21 forks source link

Injection #191

Open SheetKey opened 1 year ago

SheetKey commented 1 year ago

The current way I'm designing a game is to have some game state that gets passed between SNs, and is then looped back via the Feedback constructor. Having these updates happen at different rates caused issues. If the beginning of the SN is faster than the end, then the front is not updating the game state received from the end, as the end has not ticked yet and has not passed the new state through for Feedback. Practically this cased lots of visual stuttering when updating player position.

As a solution I propose Injection and SeqInjection SN constructors, with accompanying clocks and whatnot. The idea is to have a series of SNs that recieve "injected" data and update the state based on the data. The type signature of SeqInjection requires that these "update SNs" all have the same clock, so they can all tick together, no ResBuf required. The Injection constructor is almost identical to Sequential, except for the clock type and that the injecting SN must have input ().

The SeqInjection constructor allows for Injections and SeqInjections to be scheduled together in any order.

The idea is to have injections that create a change in position or health or whatever regardless of the current state and then have the updates take place safely, such that every part of the program that needs the game state has to most updated part.

turion commented 1 year ago

Wow, this PR is complete with example and haddocks, has high code quality and matches the existing code style. Basically a maintainers dream! Thank you!

The only thing preventing me from merging it is something you can't know: How it would fit into the long-term picture. You've probably seen now that some functions' implementation size is quadratic in the number of SN constructors, so every additional one counts. I definitely want rhine to be as expressive as possible, so if there is some useful dataflow that the current set of combinators doesn't support, we need a new one. But if it is possible to express your use case with the existing constructors, we shouldn't add a new one, and instead reduce this PR to just supplying the combinator and the example. I've tinkered around with the type signature of Injection a bit and am still undecided, but I hope I'll get to the solution these days. In general I believe that the current set of constructors is too complicated and not expressive, and that there can be some simplification. But I have to merge https://github.com/turion/rhine/pull/171 first, then we're rid of schedules and everything is a bit simpler. In short: It might be that at some point Injection will be removed again and replaced by something more basic, and this could happen before we merge this PR here.

If you want you can have a look in parallel whether your problem can be solved with the existing code: Have a look at https://github.com/turion/rhine/pull/187 where there is a new constructor that I'll most probably merge, that is simpler than your Injection. Maybe it is possible to express what you need in terms of it, but I'm not sure yet.

The current way I'm designing a game is to have some game state that gets passed between SNs, and is then looped back via the Feedback constructor. Having these updates happen at different rates caused issues. If the beginning of the SN is faster than the end, then the front is not updating the game state received from the end, as the end has not ticked yet and has not passed the new state through for Feedback. Practically this cased lots of visual stuttering when updating player position.

I'm a bit puzzled still. For a game I'd typically expect:

inputs @@ inputEventClock >-- fifoUnbounded -@- sched --> gameLogic >-- keepLast initialState -@- sched --> display @@ displayClock

I haven't understood yet where you need Feedback. Can you maybe boil down your game to the very essence (similar to your Injection example) and add it here as a further file? Possibly we can figure out a simplification somehow.

SheetKey commented 1 year ago

The idea for my game is to represent every game object with the same data type, Entity and have by game state be a vector of Entitys. The entity type will have lots of components wrapped in Maybe that keep track of anything any game object might need. I.e., the player and a ui element both have a screen position, but the ui doesn't have a velocity, so the ui element's velocity component will be Nothing. The plan was then to have roughly one SN per component. This seems like a very flexible system that makes adding new components much easier.

Additionally, rather than collect all the input in the same place, each component SN would collect and handle its own input. So rather than have a system like you mentioned, I'd have something like:

velInPut :: SN m InputClock () KeysPressed

velocityComp :: SN m cl GameState GameState
velocityComp = -- Get the game state, compose it with velInPut, update game state

gameLoop = Feedback (velocityComp --> positionComp --> collisionComp --> etc --> display)

(I've omitted the resbufs and schedules but I hope the idea is clear.) I have lots of little pieces that can work independently, but all want to have the most recent game state, since each component must have type GameState -> GameState. The issue I mentioned is that I had some components updating the state faster than others, so every desynchronized and there was never a consistent GameState.

My solution was to have the state be updated everywhere at the same rate, by the computation of what to update to happen at different rates. So now components would have the form

comp :: SN m (ParallelClock m updateSpeed internalSpeed) GameState GameState

So with all my components having the same updateSpeed, the issue became a scheduling one: how to deterministically schedule nested sequential and parallel clocks. I came up with this,

duplicateDualTick :: Monad m => MSF m () (time, Either (Either a b) c)             
                  -> MSF m () (time, Either (Either a b) (Either a c))             
duplicateDualTick runningClock = concatS $ runningClock >>> arr dupA               
  where                                                                            
    dupA (time, Left (Left  a)) = [ (time, Left (Left a)), (time, Right (Left a)) ]
    dupA (time, Left (Right b)) = [ (time, Left (Right b)) ]                       
    dupA (time, Right c)        = [ (time, Right (Right c)) ]                      

schedDualPar :: Monad m                                                            
             => Schedule m (ParClock m cla clb) clc                                
             -> Schedule m (ParClock m cla clb) (ParClock m cla clc)               
schedDualPar sched = Schedule $ \parab parac -> do                                 
  let clc = parallelCl2 parac                                                      
  (runningClock, initTime) <- (initSchedule sched) parab clc                       
  return (duplicateDualTick runningClock, initTime)                                

for scheduling two parallel clocks with the same updateSpeed, but got stuch trying to generalize this to arbitrary clock structure. I created some type families to determine all the clocks had the same leftmost part, but it seemed to complicated.

So my final idea was to let clock erasure take care of this. That is the purpose of SeqInjection. The updateSpeed parts of the component SNs will all tick together, but they can receive information from different clock speeds. The Feedback constructor can now pass the most updated GameState back to the beginning of the loop, and it will be updated in the left-to-right order, as specified in the construction of SeqInjections.

Sorry that's so long but I hope it explains my goal. I'll have to look into it more but the massive changes in scheduling might do the trick. Additionally FirstResampling looks like a great addition!

turion commented 1 year ago

I've come to the conclusion that indeed what Injection does cannot be achieved with the existing constructors. This leaves these options:

  1. Merge your PR mostly as is, resolving some remaining issues
  2. Merge a generalization/adaption of your PR (see further below)
  3. Find a workaround/different architecture for your project and generalise SNs in some other way

SeqInjection

Let me draw ASCII representations of the data flow diagrams:

Injection

     ()--> sn1 --b--> rb ----> sn2 d--->
  a-----------------------/

SeqInjection (of two Injections)

                  ()--> sn12 --b''--> rb2 -----> sn22 c--->
     ()--> sn11 --b'--> rb1 -----> sn21 b---/
  a---------------------------/

What I don't understand now is how SeqInjection can be. Consider:


SeqInjection sn1 sn2
  where
    sn1 :: SN m (InjectionClock m clL cl1) a b
    sn1 = Injection sn11 rb1 sn21
    sn2 :: SN m (InjectionClock m clR cl1) b c
    sn2 = Injection sn12 rb2 sn22

sn21 produces b at rate Out cl1, but sn22 needs to consume it at rate In cl2! How can this be?

Generalisation

It bothers me a bit that

  1. we have two constructors ending up in InjectionClock
  2. the first SN in Injection has input ()

I'm thinking that this might be a symptom of being able to generalize further. Here is a possible generalization:

{-
@
a ---> sn1 ---> b
        |
        c
        |
        v
        rb
        |
        d
        |
        v
e ----->sn2 ---> f
@
-}
  Compose
    :: SN m cl1 a (b, c)
    -> ResBuf m cl1 cl2 c d
    -> SN m cl2 (d, e) f
    -> SN m (ParClock m cl1 cl2) (a, e) (Either b f)

I took inspiration from Injection and made it more general and symmetric. Does it make sense like this to you? One should recover Injection morally by setting a and b to (), and "silently dropping ()s". The only issue with it for you might be that it is now on a ParallelClock and not an InjectionClock, which means that inputs occur more often...

I'll answer more later!

SheetKey commented 1 year ago

That makes sense. I still like the idea of having a SN that has an internal clock, not visible to other SNs when composing them. A possible alternative generalization that would keep this idea is

Injection
  :: ResBuf m (In cl1) (In cl2) b c
  -> SN m cl2 c d
  -> ResBuf m (Out cl2) (In cl1) d e
  -> SN m cl1 (a, e) f
  -> SN m (InternalClock m cl2 cl1) (a, b) f

InternalClock may be the same as InjectionClock, but the idea is that In and Out don't depend on cl2, only cl1. This is more messy than Compose, and might not be any more useful.

My main reason for this is scheduling, and that was why I created SeqInjection. The issue you mentioned might be fixed by adding the constraint (Out cl1) ~ (In cl1) to SeqInjection. However, I do realize that two constructors is a lot to ask for, especially since SeqInjection doesn't do much and is entirely about scheduling. As you previously said, it would likely be removed in the future with scheduling changes.

I've played around with schedules a bit more and have something that might allow for the deterministic scheduling of sequentially composed parallel clocks, making Compose exactly what I'd like.

schedDualPar :: Monad m
             => Schedule m (ParClock m cla clb) clc
             -> Schedule m (ParClock m cla clb) (ParClock m cla clc)
schedDualPar sched = Schedule $ \parab parac -> do
  let clc = parallelCl2 parac
  (runningClock, initTime) <- (initSchedule sched) parab clc
  return (duplicateDualTick runningClock, initTime)

schedParLeftSeq
  :: (Monad m
     , Time cla ~ Time clb
     )
  => Schedule m clb (SeqClock m (ParClock m cla clc) cld)
  -> Schedule m (ParClock m cla clb) (SeqClock m (ParClock m cla clc) cld)
schedParLeftSeq sched = Schedule $ \par seq -> do
  let clb = parallelCl2 par
  (runningClock, initTime) <- (initSchedule sched) clb seq
  return (duplicateLeftCla runningClock, initTime)

duplicateDualTick :: Monad m
                  => MSF m () (time, Either (Either a b) c)
                  -> MSF m () (time, Either (Either a b) (Either a c))
duplicateDualTick runningClock = concatS $ runningClock >>> arr dupA
  where
    dupA (time, Left (Left  a)) = [ (time, Left (Left a)), (time, Right (Left a)) ]
    dupA (time, Left (Right b)) = [ (time, Left (Right b)) ]
    dupA (time, Right c)        = [ (time, Right (Right c)) ]

duplicateLeftCla
  :: Monad m
  => MSF m () (time, Either b (Either (Either a c) d))
  -> MSF m () (time, Either (Either a b) (Either (Either a c) d))
duplicateLeftCla runningClock = concatS $ runningClock >>> arr dupA
  where
    dupA (time, Left b) = [ (time, Left (Right b)) ]
    dupA (time, Right (Left (Left a))) = [ (time, Left (Left a)), (time, Right (Left (Left a))) ]
    dupA (time, Right x) = [ (time, Right x) ]

schedDualPar takes care of the base case of scheduling two Composes sequentially and schedParLeftSeq takes care of prepending more Composes. (The types are off currently as these schedule clL not clR but the concept is the same.)

turion commented 1 year ago

Let me ask further about the goal you want to achieve.

The plan was then to have roughly one SN per component.

I don't understand why that is necessary. How does a component need several clocks? My intuition would have been to have one ClSF per component.

The issue I mentioned is that I had some components updating the state faster than others,

The current way I'm designing a game is to have some game state that gets passed between SNs, and is then looped back via the Feedback constructor.

I guess that's what I don't yet understand. Is it really necessary to pass state between different clock rates? Or can we not keep the game state on one clock? It is fine to have individual components on individual clocks, as long as only their individual dynamics is modeled there. Passing around the whole gamestate to all components seems like the wrong approach to me. I'd suggest something more like this (pseudocode):

comp1 :: ClSF m cl1 Interaction ComponentState
comp2 :: ClSF m cl2 Interaction ComponentState
comp3 :: ClSF m cl3 Interaction ComponentState

interactions :: ClSF m clSim [ComponentState] (GameState, [Interaction])

(Feedback someBuffer $ (comp1 |||| comp2 |||| comp3) >-- buf -@- sched --> interactions) >-- buf -@- sched --> display

interactions is the global simulation and takes care of interactions of the individual components (say, collision detection), and broadcasts those interactions back to the components via feedback. This way, only one component holds the complete game state, thus it stays consistent.

This is all high level and abstract, I hope it makes a bit of sense to you. Maybe it is possible to redesign your architecture a bit such that you won't need other SN constructors yet.

SheetKey commented 1 year ago

That design makes sense but has the same issue I think. It won't matter if a component clock ticks twice as fast as clSim, since the component only receives new interactions when clSim ticks. If the game state is only updated in one place, then the rate of components that depend on the state seems locked at the same speed. A component that doesn't depend on state and only outputs deltas could tick at another speed, but this seems limited.

I'm considering using the Apecs library with rhine. Apecs essentially takes all the game state and sticks it into a RWST-esque transformer. This would allow be to just have individual component SNs and compose them in parallel, eliminating the need for something like interactions. If I go this route I wouldn't need to worry about something like Injection, since each piece can just work on its own, and game state is just synchronized without any thought.

turion commented 1 year ago

I'm considering using the Apecs library with rhine. Apecs essentially takes all the game state and sticks it into a RWST-esque transformer.

Yes, that may be a good idea. Use the monad for sharing state instead of passing it around. Global state can live well in a monad, while local state is ideally in a ClSF or a ResamplingBuffer.