
How do I make a Behavior of a bouncing motion? I want to reverse the velocity when the object goes beyond a certain position, but since the position depends on the velocity, I have a loop. Is there a way to make recursive behaviors, or am I going about this all wrong? bouncingPosition :: Behavior Double bouncingPosition = ??? bouncingVelocity :: Double -> Behavior TimeT -> Behavior Double bouncingVelocity v0 t = velocityB v0 t `switcher` ??? collision :: Event a -> Behavior Double -> Event Double collision e = once . filterMP (< -2) . snapshot_ e positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t velocityB :: Double -> Behavior Double -> Behavior Double velocityB v0 t = velocity v0 <$> t velocity :: Double -> TimeT -> Double velocity v0 t = v0 - 9.8 * t Thanks, Greg

Hi Greg.
I'd use a couple of integrals and a snapshot, and the result would indeed be
recursive. I carefully designed the semantics of reactivity to make this
sort of thing possible. In particular, switcher switches immediately after
event occurrences. Not "one tick" or some such (since Reactive is based on
continuous time), but really immediately. Thus snapshotting a behavior at
the moment it switches gets the pre-event-occurrence value. This sort of
formulation worked fine in Fran and was great fun.
Now here's the temporary bad news: Currently, there's a bug in the Reactive
implementation, and this sort of (recursive) example locks up. :( Creighton
is looking into it. http://trac.haskell.org/reactive/ticket/1 .
- Conal
On Thu, Nov 20, 2008 at 5:35 PM, Greg Fitzgerald
How do I make a Behavior of a bouncing motion? I want to reverse the velocity when the object goes beyond a certain position, but since the position depends on the velocity, I have a loop. Is there a way to make recursive behaviors, or am I going about this all wrong?
bouncingPosition :: Behavior Double bouncingPosition = ???
bouncingVelocity :: Double -> Behavior TimeT -> Behavior Double bouncingVelocity v0 t = velocityB v0 t `switcher` ???
collision :: Event a -> Behavior Double -> Event Double collision e = once . filterMP (< -2) . snapshot_ e
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
velocityB :: Double -> Behavior Double -> Behavior Double velocityB v0 t = velocity v0 <$> t
velocity :: Double -> TimeT -> Double velocity v0 t = v0 - 9.8 * t
Thanks, Greg _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Thanks Conal, this library is really looking great.
-Greg
On Thu, Nov 20, 2008 at 6:19 PM, Conal Elliott
Hi Greg.
I'd use a couple of integrals and a snapshot, and the result would indeed be recursive. I carefully designed the semantics of reactivity to make this sort of thing possible. In particular, switcher switches immediately after event occurrences. Not "one tick" or some such (since Reactive is based on continuous time), but really immediately. Thus snapshotting a behavior at the moment it switches gets the pre-event-occurrence value. This sort of formulation worked fine in Fran and was great fun.
Now here's the temporary bad news: Currently, there's a bug in the Reactive implementation, and this sort of (recursive) example locks up. :( Creighton is looking into it. http://trac.haskell.org/reactive/ticket/1 .
- Conal
On Thu, Nov 20, 2008 at 5:35 PM, Greg Fitzgerald
wrote: How do I make a Behavior of a bouncing motion? I want to reverse the velocity when the object goes beyond a certain position, but since the position depends on the velocity, I have a loop. Is there a way to make recursive behaviors, or am I going about this all wrong?
bouncingPosition :: Behavior Double bouncingPosition = ???
bouncingVelocity :: Double -> Behavior TimeT -> Behavior Double bouncingVelocity v0 t = velocityB v0 t `switcher` ???
collision :: Event a -> Behavior Double -> Event Double collision e = once . filterMP (< -2) . snapshot_ e
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
velocityB :: Double -> Behavior Double -> Behavior Double velocityB v0 t = velocity v0 <$> t
velocity :: Double -> TimeT -> Double velocity v0 t = v0 - 9.8 * t
Thanks, Greg _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead: positionB x0 v t = (x0 +) <$> (v <^(*)^> t) Hope that helps Bob

For that matter, you can also say, thanks to Num overloading:
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double
positionB x0 v t = pure x0 + v * t
Sadly, similar convenience does not come for free with non-methods, such as
most of the FieldTrip API. For non-methods, in the past (with Fran), I've
written parallel sets of modules with behavior-lifted functionality. It's
tedious to set up but convenient to use. Perhaps a tool could automate the
job.
By the way, a nice feature of Yampa is that it avoids this lifting business
altogether, via desugaring for the arrow notation.
- Conal
On Fri, Nov 21, 2008 at 12:14 AM, Thomas Davie
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead:
positionB x0 v t = (x0 +) <$> (v <^(*)^> t)
Hope that helps
Bob
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t positionB x0 v t = pure x0 + v * t
That's very convenient. I'm showing this stuff off to visual
designers, so tricks like this have great Sales appeal. :)
If others are trying this out, the Num instance is implemented in
FRP.Reactive.Num.
-Greg
On Fri, Nov 21, 2008 at 6:48 AM, Conal Elliott
For that matter, you can also say, thanks to Num overloading:
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = pure x0 + v * t
Sadly, similar convenience does not come for free with non-methods, such as most of the FieldTrip API. For non-methods, in the past (with Fran), I've written parallel sets of modules with behavior-lifted functionality. It's tedious to set up but convenient to use. Perhaps a tool could automate the job.
By the way, a nice feature of Yampa is that it avoids this lifting business altogether, via desugaring for the arrow notation.
- Conal
On Fri, Nov 21, 2008 at 12:14 AM, Thomas Davie
wrote: positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead:
positionB x0 v t = (x0 +) <$> (v <^(*)^> t)
Hope that helps
Bob _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Shouldn't Reactive also have VectorSpace instances for Behaviors of VectorSpace elements? So that the code becomes
positionB x0 v t = pure x0 ^+^ v ^* t
Maybe it already has, in that case, sorry for the spam ;)
On Fri, Nov 21, 2008 at 7:00 PM, Greg Fitzgerald
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t positionB x0 v t = pure x0 + v * t
That's very convenient. I'm showing this stuff off to visual designers, so tricks like this have great Sales appeal. :)
If others are trying this out, the Num instance is implemented in FRP.Reactive.Num.
-Greg
For that matter, you can also say, thanks to Num overloading:
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = pure x0 + v * t
Sadly, similar convenience does not come for free with non-methods, such as most of the FieldTrip API. For non-methods, in the past (with Fran), I've written parallel sets of modules with behavior-lifted functionality. It's tedious to set up but convenient to use. Perhaps a tool could automate
On Fri, Nov 21, 2008 at 6:48 AM, Conal Elliott
wrote: the job.
By the way, a nice feature of Yampa is that it avoids this lifting business altogether, via desugaring for the arrow notation.
- Conal
On Fri, Nov 21, 2008 at 12:14 AM, Thomas Davie
wrote: positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead:
positionB x0 v t = (x0 +) <$> (v <^(*)^> t)
Hope that helps
Bob _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Good point. There is already a VectorSpace instance for behaviors, and
using it in the positionB definition makes for a much more general type.
See FRP.Reactive.VectorSpace.
I wouldn't use v ^* t (or t *^ v), however, because v is dynamic.
Integrating v ought to do the trick.
And I expect that any simple & direct formulation will run into the current
implementation bug with recursive behaviors, since the position depends on
the velocity, the velocity depends on acceleration and accumulated impulse,
and the accumulated impulse depends on position.
- Conal
On Fri, Nov 21, 2008 at 11:33 AM, Peter Verswyvelen
Shouldn't Reactive also have VectorSpace instances for Behaviors of VectorSpace elements? So that the code becomes
positionB x0 v t = pure x0 ^+^ v ^* t
Maybe it already has, in that case, sorry for the spam ;)
On Fri, Nov 21, 2008 at 7:00 PM, Greg Fitzgerald
wrote: positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t positionB x0 v t = pure x0 + v * t
That's very convenient. I'm showing this stuff off to visual designers, so tricks like this have great Sales appeal. :)
If others are trying this out, the Num instance is implemented in FRP.Reactive.Num.
-Greg
For that matter, you can also say, thanks to Num overloading:
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = pure x0 + v * t
Sadly, similar convenience does not come for free with non-methods, such as most of the FieldTrip API. For non-methods, in the past (with Fran), I've written parallel sets of modules with behavior-lifted functionality. It's tedious to set up but convenient to use. Perhaps a tool could automate
On Fri, Nov 21, 2008 at 6:48 AM, Conal Elliott
wrote: the job.
By the way, a nice feature of Yampa is that it avoids this lifting business altogether, via desugaring for the arrow notation.
- Conal
On Fri, Nov 21, 2008 at 12:14 AM, Thomas Davie
wrote: positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead:
positionB x0 v t = (x0 +) <$> (v <^(*)^> t)
Hope that helps
Bob _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

I have bouncing balls balls working now (code below). It uses scanlB
instead of a recursive behavior.
Here's the ugliest part, and I'd love to hear suggestions about it:
scanlB const beh ((\((_x,_v),t) -> bounce xLow xLow (12) t) <$>
collisions xLow event beh)
Ideally, I'd like to pass the next 'bounce' variables 'x' and '-v'
from the previous behavior instead of 'xLow' and '12', but because 'x'
is below 'xLow', it triggers a collision. If I pass 'xLow' and '-v',
then the balls bounce higher and higher from the extra speed gained
between 'xLow' and 'x'. So I need to either figure out a way to
filter collisions until 'x' is above 'xLow' again, or start bounce at
'xLow' and figure out what the velocity would have been at that
position.
The next ugliest line is this:
event = withTimeE_ (atTimes (map (t0+) [0,0.01..]))
Should I be using 'framePass' here?
import Data.Monoid
import Control.Applicative
import FRP.Reactive
import FRP.Reactive.GLUT.Adapter
import Graphics.FieldTrip
import FRP.Reactive.FieldTrip.Adapter
main :: IO ()
main = anim3 $ \ui -> drops_ 0.25 lilRedBall (leftButtonPressed ui)
`mappend` drops_ 0.5 lilGreenBall (leftButtonPressed ui)
lilRedBall :: Double -> Geometry3
lilRedBall sz = lilThing red (-1) sz (flatG udisk)
lilGreenBall :: Double -> Geometry3
lilGreenBall sz = lilThing green 1 sz (flatG udisk)
lilThing :: Col -> Double -> Double -> Geometry3 -> Geometry3
lilThing color x sz = materialG (flat color) . (translate3 (Vector3 x
0 0) *%) . (uscale3 sz *%)
drops_ :: Double -> (Double -> Geometry3) -> Event a -> Behavior Geometry3
drops_ sz g0 e = monoidB ((fmap . fmap) (object (g0 sz)) bouncing)
where
bouncing = bounce 0 (-2.5+sz) 0 <$> withTimeE_ e
object :: Geometry3 -> (Double,Double) -> Geometry3
object g0 (pos,_y) = translate3 (Vector3 0 pos 0) *% g0
bounce :: Double -> Double -> Double -> TimeT -> Behavior (Double, Double)
bounce x0 xLow v0 t0 = scanlB const beh ((\((_x,_v),t) -> bounce xLow
xLow (12) t) <$> collisions xLow event beh)
where
event = withTimeE_ (atTimes (map (t0+) [0,0.01..]))
beh = fall x0 v0 t0
fall :: Double -> Double -> Double -> Behavior (Double, Double)
fall x0 v0 t0 = gravity x0 v0 <$> (subtract t0 <$> time)
collisions :: Double -> Event a -> Behavior (Double,Double) -> Event
((Double,Double), TimeT)
collisions xLow e = withTimeE . once . filterMP (\(x,_) -> x < xLow) .
snapshot_ e
gravity :: Double -> Double -> TimeT -> (Double, Double)
gravity x v t = (x + v * t - 9.8 * (t * t), -9.8 * t)
On Fri, Nov 21, 2008 at 10:00 AM, Greg Fitzgerald
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t positionB x0 v t = pure x0 + v * t
That's very convenient. I'm showing this stuff off to visual designers, so tricks like this have great Sales appeal. :)
If others are trying this out, the Num instance is implemented in FRP.Reactive.Num.
-Greg
On Fri, Nov 21, 2008 at 6:48 AM, Conal Elliott
wrote: For that matter, you can also say, thanks to Num overloading:
positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = pure x0 + v * t
Sadly, similar convenience does not come for free with non-methods, such as most of the FieldTrip API. For non-methods, in the past (with Fran), I've written parallel sets of modules with behavior-lifted functionality. It's tedious to set up but convenient to use. Perhaps a tool could automate the job.
By the way, a nice feature of Yampa is that it avoids this lifting business altogether, via desugaring for the arrow notation.
- Conal
On Fri, Nov 21, 2008 at 12:14 AM, Thomas Davie
wrote: positionB :: Double -> Behavior Double -> Behavior Double -> Behavior Double positionB x0 v t = (x0 +) <$> liftA2 (*) v t
On an unrelated note, I created a package called InfixApplicative, because I found that exactly this kind of expression looked ugly in my code. If you import it, you can define this instead:
positionB x0 v t = (x0 +) <$> (v <^(*)^> t)
Hope that helps
Bob _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

I fixed the collision issue (I should have failed first year physics). gravity :: Double -> Double -> TimeT -> (Double, Double) gravity x0 v0 t = (x0 + v0 * t - 4.9 * (t * t), v0 - 9.8 * t) New code here: http://hpaste.org/12263 But this is still unusable. There's a massive space leak somewhere, and the program continues to grow even after you close the window! Anyone have any pointers for tracking this down? -Greg

well, Bob and I also found a space leak in Tetris, and as far as I
understood it a lot of MVars and (,) are leaking, probably because something
is sticking on the head of the reactive streams or something so they can't
be garbage collected, or some "push" events streams lack observers so they
keep growing. But it's still unclear. I'm making a very small program here
to reproduce the problem; I'm not using anything from Reactive but unamb and
I also have a space leak, but that might be because of some bugs in my test
case...
On Fri, Nov 21, 2008 at 10:57 PM, Greg Fitzgerald
I fixed the collision issue (I should have failed first year physics).
gravity :: Double -> Double -> TimeT -> (Double, Double) gravity x0 v0 t = (x0 + v0 * t - 4.9 * (t * t), v0 - 9.8 * t)
New code here: http://hpaste.org/12263
But this is still unusable. There's a massive space leak somewhere, and the program continues to grow even after you close the window! Anyone have any pointers for tracking this down?
-Greg _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

I'd love to see simple test cases that exhibit space leaks (or other
oddities). Please contribute findings to the Reactive tracker:
http://trac.haskell.org/reactive/report/1?sort=ticket&asc=1 . - Conal
2008/11/21 Peter Verswyvelen
well, Bob and I also found a space leak in Tetris, and as far as I understood it a lot of MVars and (,) are leaking, probably because something is sticking on the head of the reactive streams or something so they can't be garbage collected, or some "push" events streams lack observers so they keep growing. But it's still unclear. I'm making a very small program here to reproduce the problem; I'm not using anything from Reactive but unamb and I also have a space leak, but that might be because of some bugs in my test case...
On Fri, Nov 21, 2008 at 10:57 PM, Greg Fitzgerald
wrote: I fixed the collision issue (I should have failed first year physics).
gravity :: Double -> Double -> TimeT -> (Double, Double) gravity x0 v0 t = (x0 + v0 * t - 4.9 * (t * t), v0 - 9.8 * t)
New code here: http://hpaste.org/12263
But this is still unusable. There's a massive space leak somewhere, and the program continues to grow even after you close the window! Anyone have any pointers for tracking this down?
-Greg _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
participants (4)
-
Conal Elliott
-
Greg Fitzgerald
-
Peter Verswyvelen
-
Thomas Davie