atzeus / FRPNow

Other
89 stars 14 forks source link

Infinite recursion (stack blown) with mutual recursion in event streams #7

Open ocharles opened 9 years ago

ocharles commented 9 years ago

Here is a minimal example program:

{-# LANGUAGE RecursiveDo #-}

import Control.FRPNow
import Control.Monad
import System.IO

main :: IO ()
main =
  do hSetBuffering stdin NoBuffering
     hSetBuffering stdout NoBuffering
     runNowMaster
       (mdo (keyPressed,keyPress) <- callbackStream
            -- State begins in state "1", and when a key is pressed it switches to state 2
            state <-
              sample (fromChanges
                        1
                        (2 <$ (keyPressed `during` (fmap (1 ==) state))))
            -- Whenever the state changes, print it
            callIOStream (print :: Int -> IO ())
                         (toChanges state)
            async (forever (getChar >>= keyPress)))

When ran, if you press any key the process begins using all the memory it can, until it blows the stack.

If I change fmap (1 ==) state to pure True it works fine, but obviously is a different program :) Perhaps a missing call to futuristic somewhere?

ocharles commented 9 years ago

Another example using snapshots:

{-# LANGUAGE RecursiveDo #-}

import Control.FRPNow
import Control.Monad
import System.IO

main :: IO ()
main =
  do hSetBuffering stdin NoBuffering
     hSetBuffering stdout NoBuffering
     runNowMaster
       (mdo (keyPressed,keyPress) <- callbackStream
            let toggles =
                  fmap not (snapshots checked (void keyPressed))
            checked <-
              sample (fromChanges False toggles)
            -- Whenever the state changes, print it
            callIOStream print
                         (toChanges checked)
            async (forever (getChar >>= keyPress)))
ocharles commented 8 years ago

I've continued to shrink the example down to try and see if I can solve the problem:

{-# LANGUAGE RecursiveDo #-}

import Control.FRPNow
import Control.Monad

main :: IO ()
main =
  runNowMaster
    (mdo run <- async (return ())
         let checked =
               pure False `switch` (fmap not checked <$ run)
         sample (whenJust (fmap guard checked)))

This might not make sense, because that might be basically saying

checked = not checked 

Using prev doesn't solve the problem though:

{-# LANGUAGE RecursiveDo #-}

import Control.FRPNow
import Control.Monad

main :: IO ()
main =
  runNowMaster
    (mdo run <- async (return ())
         let checked =
               pure False `switch` (fmap not lastChecked <$ run)
         lastChecked <-
           sample (prev False checked)
         sampleNow (whenJust (fmap guard checked)))
atzeus commented 8 years ago

Thanks, for the bugs. Which version of GHC are you using? I'm on holiday now, so it might take a while before I have time to fix this.

ocharles commented 8 years ago

This is 7.10.1. Out of interest, how long are you on holiday for? Not intended to be pushy, just curious when I should internally reschedule more frpnow experiments :)

atzeus commented 8 years ago

Ok 7.10.1 is also what I'm using. Till the 12 th of August I'm afraid. I'll contact you when I have more info. Cheers!

ocharles commented 8 years ago

No worries, have a great holiday! I'll carry on getting my hands dirty, it's good fun :)

atzeus commented 8 years ago

Great to hear that your enjoying messing around with this :)

Looking closer at your examples, I think all, except the last which uses prev, are expected to give bottom (i.e. infinite loop).

The confusion is understandable, since this is not yet described anywhere.

In FRPNow, a fixpoint is only defined if the value of a behavior at a time t does not depend on the value of that behavior itself at time t.

In your first example, the behavior state when the key is pressed at time t, is 2 if state is 1 at time t (the value of the behavior at time t depends on its own value at time t). In your second example, the same thing is happening: the value of checked when a key is pressed (at time t) is not the checked at time t. In your third example, it is as you say:

checked = not <$> checked

Using prev should help however, there must be a bug in it's implementation, which I will try to fix now.

atzeus commented 8 years ago

In the meantime, try using delay from Control.FRPNow.Time, which delays the given behavior by one tick of the "clock" . Delay will always give you the value of the behavior at the previous event.

atzeus commented 8 years ago

I think your prev example can be simplified to:

mdo let i = not <$> j
    j <- prev False i
    ....

The expected behavior, I think is that i = pure True and j = pure False. The difference with your example is that you get to this situation only after an event.

The problem is now that the event that i changes is the event that j changes is the event that i changes. Tricky!

ocharles commented 8 years ago

I think it's a shame if we do end up in this situation where it's possible to write infinite loops - we deal with this in reactive-banana by having events change instantaneously after behaviors. Eventually this all works out, and I haven't managed to build a looping program in r-b just by composing primitives (e.g., the above does work out as expected).

I'll have a play with Control.FRPNow.Time, I haven't looked at that yet.

atzeus commented 8 years ago

You have a point there, might be worth rethinking this behavior.

ocharles commented 8 years ago

https://stackoverflow.com/questions/26980819/why-does-changes-return-event-t-future-a/26996387#26996387 is the relevant Stack Overflow answer I was thinking of too, which shows that observing the changes to a behavior happens at a different time. There's also this documentation comment:

https://hackage.haskell.org/package/reactive-banana-0.4.2.0/docs/Reactive-Banana-Model.html#v%3astepper

Which goes with this longer SO answer: https://stackoverflow.com/questions/7850389/can-reactive-banana-handle-cycles-in-the-network/7852344#7852344

That might provide some food for thought!

ocharles commented 8 years ago

Paging @HeinrichApfelmus in case he wants to chime in :)

HeinrichApfelmus commented 8 years ago

The StackOverflow answers sum up my take on this pretty well. :smile:

But actually, the idea of letting a Behavior have the old value for t <= t0 and take on the new value for t > t0 goes way back to Conal Elliott's original design. The consequence is that recursion is always possible as long as it is a mutual recursion between Behavior and Event.

In addition, I have found that this approach also solves a lot of problems when trying to do a push-driven implementation.

atzeus commented 8 years ago

Thanks for the info! Where in Conal's design does it state this?

HeinrichApfelmus commented 8 years ago

In the 1997 paper "Functional Reactive Animation", section 2.2, paragraph "Reactivity", the 'smaller or equal' sign is placed exactly in this way (The setup is a little different, but this is the moral equivalent.) It's hard to notice if you're not looking for it, but in a helpful email exchange, Conal has pointed me to this subtlety and that it allows mutual recursion.

atzeus commented 8 years ago

Thanks for the subtlety!

There is a subtle design space here: On the one hand, it is nice if simple recursive things do not give bottom. Indeed, if we take the denotation of switch to be:

 switch b (t,e) = \now -> if now <= t then b now else e now

instead of what frpnow does:

switch b (t,e) = \now -> if now < t then b now else e now

Then indeed we can give more directly defined recursive a non-bottom value.

However, the actual switch then occurs at t + an infinitesimally small value. In Functional Reactive Animation, the semantics are such that there is a distinction between the idealized semantics, where sampling rate goes to infinity, and the actual semantics, which depend on the sampling rate that happened to be chosen at runtime. The idealized semantics then does not give us precisely what is actually going to happen.

In frpnow, the semantics do not depend on the sampling rate: it is impossible to observe a change in time (unless we have behavior that gives the time) which avoids this caveat

Changing the semantics of switch reintroduces this caveat: it now becomes possible to observe a change in time for example we can make the following function:

  delay :: Eq a => a -> Behavior a -> Behavior (Behavior a)

Which delays a behavior by an infinitesimally small amount of time, by using whenJust and switch. We can achieve this by observing when the input behavior changes using whenJust, and then mimicking that behavior using switch. We can then again observe a infinitesimally small amount of time, by for example checking when b and delay b differ.

On the more practical side, in frpnow currently all changes come from some outside change, such that if we have for example a gui in which no animation is shown, we do not have to update all the time, only after something actually happens. Allowing the user to observe a change in time makes this much harder to pull of.

For these reasons, i think it is better to leave switch as it is and instead use the following new function 0.16for immediate feedback loops:

   delay :: EvStream x -> a -> Behavior a -> Behavior (Behavior a)

Which delays the behavior by on tick of the clock''. Since a change in time itself is not observable, we have to provide an event stream which gives theclock''.

For example:

givesTrue :: Behavior (Behavior Bool)
givesTrue = join $
     mdo let i = not <$> j
              j <- delay emptyEs False i
              return i

gives a behavior which is always true.

Of course, reasonable people may disagree about this. Also, the situation in reactive banana may be different :) Let me know what you guys think!

HeinrichApfelmus commented 8 years ago

Well, it works just fine in reactive-banana, everything is independent of the sampling rate. That said, reactive-banana doesn't offer the whenJust function.

Are you sure that delay allows you to delay a Behavior an infinitesimal amount of time? I thought that if switch has the t <= semantics, then the only way to build Behaviors is with t <= and delay is essentially the identity. A concrete definition of delay would be helpful.

Xandaros commented 8 years ago

Well, in my snake game I am adding delays manually to prevent feedback loops and it kinda works. However, things that are meant to happen simultaneously are sometimes delayed by one game tick. (For example, when the snake eats a food pellet, the new pellet only appears after the snake moves the next time, even though it is meant to be simultaneous.) I'm not sure how to fix this or even if it can be fixed, but it would be nice if things that are meant to happen simultaneously would just do, without having to rely on manually hacking in delays.

atzeus commented 8 years ago

@HeinrichApfelmus The problem is whenJust : If we have an event, e, then the following will give us an event an infinitesimally later than, e:

 slightlyLater :: Event a -> Behavior (Event a)
 slightlyLater e = whenJust (Nothing `step` (Just <$> e))

This can be used to delay a behavior an infinitesimally small amount with the following:

 delay :: Behavior a -> Behavior (Behavior a)
 delay b = loop where
     loop = do cur <- b
                     changeEv <- whenJust (maybeNotEq cur <$> b)
                     switchEv <- plan (loop <$ changeEv)
                     return (cur `step` switchEv)
     maybeNotEq c b 
        | c == b = Nothing
        | otherwise = Just b

with the current frpnow semantics the above is equivalent to:

  delay b = pure b

@Xandaros Thanks for the link! In what places in your snake example does this turn up? Does the new function:

  delay :: EvStream x -> a -> Behavior a -> Behavior (Behavior a)

help?

HeinrichApfelmus commented 8 years ago

@atzeus Oh, so you're saying that in the denotation for whenJust, the function minSet really is a minimum over real numbers, not an infimum. Since not every set of real numbers has a minimum, I would even go as far as saying that the semantics of delay are undefined in this case. However, what happens if you also change the definition of whenJust to use an infimum? I think that everything should be fine in this case, no?

atzeus commented 8 years ago

@HeinrichApfelmus Yes indeed you are right. There was some confusion in my head :) Indeed when whenJust is defined in terms of a minimum over number and switch uses <= then the whole thing is undefined. With an infimum then indeed delay b is equivalent to pure b

atzeus commented 8 years ago

Good point, maybe you are right that this solves the problem. I'm going to think about it.

atzeus commented 8 years ago

Hmmm, actually you might be right that this is a good way to solve all this. I just got what you meant all along :)

HeinrichApfelmus commented 8 years ago

:smile: By the way, an intuitive way to check the plausibility of this approach is to note that any semantics which uses real numbers cannot contain infinitesimals. (I used to be a huge fan of non-standard analysis, though.)

That said, this approach may have a drawback at some point: I found it very difficult to make a push-based implementation of whenJust in conjunction with switch with these semantics. (An implementation that relies on polling has no issues with this.) But I think that recursion is totally worth the price.

atzeus commented 8 years ago

In some cases, it is also desirable to immediatly observe the switch. For example:

hasOccured :: Event x -> Behavior Bool
hasOccured e = pure False `switch` (pure True <$ e)

if the semantics of switch is

 switch b (t,e) = \now -> if now < t then b now else e now

Then we will immediatly see it when an event has occured, but with

 switch b (t,e) = \now -> if now <= t then b now else e now

We will not.

My current thinking is to have two switching combinators:

An immediate switching function:

switch b (t,e) = \now -> if now < t then b now else e now

And a delayed switching function:

dswitch b (t,e) = \now -> if now <= t then b now else e now

And of course change the semantics of whenJust to talk about the infinimum rather than the minimum :)

What do you guys think, is this a good idea?

dobesv commented 8 years ago

It would probably be helpful to enumerate some motivating examples for both versions before making changes too speculatively.

On Thu, Sep 24, 2015, 5:29 AM atzeus notifications@github.com wrote:

In some cases, it is also desirable to immediatly observe the switch. For example:

hasOccured :: Event x -> Behavior Bool hasOccured e = False step (pure True <$ e)

if the semantics of switch is

switch b (t,e) = \now -> if now < t then b now else e now

Then we will immediatly see it when an event has occured, but with

switch b (t,e) = \now -> if now <= t then b now else e now

We will not.

My current thinking is to have two switching combinators:

An immediate switching function:

switch b (t,e) = \now -> if now < t then b now else e now

And a delayed switching function:

dswitch b (t,e) = \now -> if now <= t then b now else e now

And of course change the semantics of whenJust to talk about the infinimum rather than the minimum :)

What do you guys think, is this a good idea?

— Reply to this email directly or view it on GitHub https://github.com/atzeus/FRPNow/issues/7#issuecomment-142914521.

HeinrichApfelmus commented 8 years ago

Well, the benefit of making dswitch the default is that recursion is always well-defined, as long as it's a mutual recursion between Event (streams) and Behavior. In a GUI setting, I essentially always end up using recursion, and it's very convenient to have it work automatically.

Sometimes, I also feel like I want to observe a change right now, but I usually model this situation with Event only instead. I agree with @dobesv that discussing this with a concrete example is a good idea.

atzeus commented 8 years ago

I agree that recursion is essentially every where.

Here's a more concrete example:

movableRect :: Rect -> Behavior Point -> Behavior (Set MouseButton) -> Behavior (Behavior Rect)
movableRect initRect mousePos buttons = 
    mdo let mouseOver = isInside <$> mousePos <*> rect
            startDrag <- clickOn rect  MLeft
            stopDrag  <- releases MLeft
            mouseVel <- diffPoint mousePos
            dragDiff <- foldrSwitch (pure (0,0)) $ 
                              (mouseVel <$ startDrag) `merge` (pure (0,0) <$ endDrag)
            pos <- foldB addPoint (0,0) dragDiff
            let rect = moveRect r <$> pos
            return rect where

  diffPoint :: Behavior Point -> Behavior (Behavior Point)
  diffPoint b = do c <- b 
                   foldB (p c -> c .- p) (0,0) ((.- c) <$> b)

  mouseOffset :: Behavior (Behavior Point)
  mouseOffset = do p <- mousePos
                   return ((.- p) <$> mousePos)

  clicks :: MouseButton -> EvStream ()
  clicks m   = edges $ (m `elem`) <$> buttons
  releases m = edges $ not . (m `elem`) <$> buttons

(.-) :: Point -> Point -> Point
(x,y) .- (x',y') = (x - x', y - y')

data Rect = Rect { leftup :: Point , rightdown :: Point }

moveRect (Rect p1 p2) m = Rect (p1 .+ m) (p2 .+ m)

isInside p (Rect c1 c2) = pointInBox p c1 c2

Which defines a draggable rectangle (+ supporting code). However, with the current switching semantics, this is not well-defined! The problem is that the position of the rectangle depends on wether the mouse is over, which again depends on the position of the rectangle.

Changing the semantics of switch to use <= instead of < fixes this, but this has another problem: changes are now never immediately visible. Consider the following:

mouseClicks :: EvStream ()

bla :: Now ()
bla = do click <- nxt mouseClick
              nrClicks <- sample $ foldEs (+) 0 mouseClicks
              let printNrClicks =
                    do sample <- nrClicks
                         sync $ putStrLn (show sample)
              plan (printNrClicks <$ click)

Using switch with <= instead of < will now print 0 instead of 1. Since both using <= and < have their up and down-sides. I propose having two switching combinators. How does reactive-banana solve this @HeinrichApfelmus ? The dragging example can then be made well-defined by using a different folding combinators which uses the decoupled switch.

HeinrichApfelmus commented 8 years ago

The observation is that in a large of number of cases, the newest value of the Behavior is only needed to perform IO actions, for instance to display the latest value of the Behavior on the screen. The solution in reactive-banana is to make a special case for this situation, and allow sampling the newest value of the Behavior under the condition that it can only be used for performing IO actions, not for doing other calculations.

Concretely, I provide a function

changes :: Behavior a -> MomentIO (EvStream (Future a))

which is similar to whenJust, but lives in the MomentIO monad, the equivalent of the Now monad. It's part of the "dirty" I/O and not considered a core combinator.

The result event contains the values of the Behavior at time > t, though put into an additional dummy type Future. This indicates that the value is not available at time == t, only later. An event stream of this kind can be fed into a function

reactimate' :: EvStream (Future (IO ())) -> MomentIO ()

which indicates that I/O actions are to be executed, similar to your async combinator.

An equivalent construction in FRPNow would be two combinators

sample' :: Behavior a -> Now (Future a)
async'  :: Future (IO a) -> Now (E a)

that allow you to obtain the newest value of the Behavior (i.e. the value that the Behavior will have at a time t2 with t2 > t instead of t2 == t where t is the current time) and perform IO actions with it. This way, it's possible to sample the newest value while still allowing recursion — the Future type is abstract and it's impossible to pattern match on the value contained therein.