reactiva-banana : how to implement a certain type of throttling

Hi list, I would like to implement a certain type of throttling of events in reactive-banana. It should work such that an event is not let through if arrives at less then delta seconds from the last event that passed through. If it is not let through then it is stored and is fired after delta seconds from the last fired event. Below is a program that implements this for lists of time stamped numbers. Would it be possible to translate this to reactive-banana ? Also, in reactive-banana how do I fire an event x seconds after some other event comes in. The way I would do it in scala’s reactive-web is to start a timer that fires x seconds after it is started when an event comes in using dynamic event switching . It seems to me this would not be possible in reactive-banana because starting a timer is an IO operation, so I assume it can’t be done inside the event/behavior logic, right ? best, Miguel Negrão module Main where import Data.List -- 1 second throtling -- logic is to never output a value before 1 second has passed since last value was outputed. main :: IO() main = print $ test [ (0.0, 1.0), (1.1, 2.0), (1.5,3.0), (1.7,4.0), (2.2, 5.0) ] --should output [ (0.0, 1.0), (1.1, 2.0), (2.1,4.0), (3.1, 5.0) ] test :: [(Double,Double)] -> [(Double,Double)] test list = g v (concat xs) where (v, xs) = mapAccumL f (-50,Nothing) list g (t, Just x) ys = ys ++ [ (t+1,x) ] g _ ys = ys f (lasttime, Just holdvalue) (t,x) = if t > (lasttime+1) then if t > (lasttime + 2) then ( (t, Nothing), [ (lasttime+1,holdvalue), (t,x)] ) else ( (lasttime+1, Just x) , [ (lasttime+1,holdvalue) ] ) else ( (lasttime, Just x), [] ) f (lasttime, Nothing) (t,x) = if t > (lasttime+1) then ( (t,Nothing) , [ (t, x ) ] ) else ( (lasttime, Just x), [] )

Miguel Negrao wrote:
Hi list,
I would like to implement a certain type of throttling of events in reactive-banana. It should work such that an event is not let through if arrives at less then delta seconds from the last event that passed through. If it is not let through then it is stored and is fired after delta seconds from the last fired event.
Below is a program that implements this for lists of time stamped numbers. Would it be possible to translate this to reactive-banana ?
Also, in reactive-banana how do I fire an event x seconds after some other event comes in. The way I would do it in scala’s reactive-web is to start a timer that fires x seconds after it is started when an event comes in using dynamic event switching . It seems to me this would not be possible in reactive-banana because starting a timer is an IO operation, so I assume it can’t be done inside the event/behavior logic, right ?
Miguel, could you repost this question on Stackoverflow, so I can answer it there? This way, questions about reactive-banana are easier to find later on. http://stackoverflow.com/questions/ask?tags=reactive-programming+haskell+frp As for the answer, it is possible to implement the functionality you desire in reactive-banana, though it is a little involved. Basically, you have use an external framework like wxHaskell to create a timer, which you can then use to schedule events. The Wave.hs example from the examples pages demonstrates how to do that. Put differently, I have opted to not include time in the reactive-banana library itself. The reason is simply that different external framework have timers of different resolution or quality, there is no one-size that fits it all. I do intend to add common helper functions that deal with time and timers to the library itself, but I still need to find a good way to make it generic over different timers and figure out which guarantees I can provide. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

A 04/06/2012, às 16:11, Heinrich Apfelmus escreveu:
Miguel, could you repost this question on Stackoverflow, so I can answer it there? This way, questions about reactive-banana are easier to find later on.
http://stackoverflow.com/questions/ask?tags=reactive-programming+haskell+frp
I’ve reposted the question here: http://stackoverflow.com/questions/10888826/reactive-banana-throttling-event...
As for the answer, it is possible to implement the functionality you desire in reactive-banana, though it is a little involved.
Basically, you have use an external framework like wxHaskell to create a timer, which you can then use to schedule events. The Wave.hs example from the examples pages demonstrates how to do that.
Put differently, I have opted to not include time in the reactive-banana library itself. The reason is simply that different external framework have timers of different resolution or quality, there is no one-size that fits it all. I do intend to add common helper functions that deal with time and timers to the library itself, but I still need to find a good way to make it generic over different timers and figure out which guarantees I can provide.
Ok, looking at Wave.hs I can see what I need to do to be able to delay an event by a certain amount of seconds. The scheduleQueue function there doesn’t exactly do what I need it to do, because it schedules relative to the last scheduled event. Essentially I would need to alter it such that the scheduling is done in absolute terms, so If I ask something to happen 5 seconds from now it should really happen 5 seconds from now instead of 5 seconds from the last event in queue. One way to do it would be to keep the scheduled times in UTC or some other time format and every time an event comes into the queue stop the timer, sort the event queue by the absolute times, check how long is it till the next event and set the timer delay to be that amount of time, then keep repeating the procedure. It would indeed be nice to have something like this already available in reactive-banana-wx, or in some timer type independent way in the library itself. Two practical question: 1) How do I filter the slider events (from event0 mySlider command) to get only one event instead of 3 every time I move the slider ? 2) What is the best way to set some wx property based on the current value of some behavior but only when some event happens ? I’m doing like this now: reactimate $ apply ((\x->(\y->set slider2 [selection := x])) <$> slider1SelectionBehavior) slider1Event best, Miguel

Miguel Negrao wrote:
A 04/06/2012, às 16:11, Heinrich Apfelmus escreveu:
Miguel, could you repost this question on Stackoverflow, so I can answer it there?
I’ve reposted the question here: [..]
Thanks!
Ok, looking at Wave.hs I can see what I need to do to be able to delay an event by a certain amount of seconds. The scheduleQueue function there doesn’t exactly do what I need it to do, because it schedules relative to the last scheduled event. Essentially I would need to alter it such that the scheduling is done in absolute terms, so If I ask something to happen 5 seconds from now it should really happen 5 seconds from now instead of 5 seconds from the last event in queue. One way to do it would be to keep the scheduled times in UTC or some other time format and every time an event comes into the queue stop the timer, sort the event queue by the absolute times, check how long is it till the next event and set the timer delay to be that amount of time, then keep repeating the procedure.
The wxTimers use relative time, so you would have to convert between the two, indeed. It's probably not straightforward, but likely an interesting exercise.
It would indeed be nice to have something like this already available in reactive-banana-wx, or in some timer type independent way in the library itself.
Henning Thielemann has written some time-related combinators in his reactive-balsa library http://hackage.haskell.org/package/reactive-balsa You can probably get some inspiration from there.
Two practical question:
1) How do I filter the slider events (from event0 mySlider command) to get only one event instead of 3 every time I move the slider ?
If they are simultaneous, then you can use collect . Otherwise, you will have to read the wxHaskell and wxWidgets documentation to figure out how to get rid of the superfluous events.
2) What is the best way to set some wx property based on the current value of some behavior but only when some event happens ? I’m doing like this now:
reactimate $ apply ((\x->(\y->set slider2 [selection := x])) <$> slider1SelectionBehavior) slider1Event
Looks good to me. You can use the <@ combinator to make it a little shorter. reactimate $ (\x -> set slider2 [ selection := x ]) <$> slider1SelectionBehavior <@ slider1Event Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (2)
-
Heinrich Apfelmus
-
Miguel Negrao