2012-06-04 52 views
7

我想实施某种类型的反应性香蕉事件抑制。它应该起作用,以使得如果从最后一次通过的事件到达的时间少于三秒,事件就不会通过。如果它没有通过,那么它将被存储并在最后一次触发事件的增量秒后触发。反应性香蕉节流事件

下面是一个程序,它实现了这个时间戳数字列表。将它翻译成反应香蕉是否可能?

另外,在反应式香蕉中,如何在某些其他事件进入后x秒钟内发射事件?

 
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), []) 

回答

1

好的,我设法实现了我在我的问题中描述的内容。我不是很高兴IO需要通过反应来控制计时器。我不知道是否有可能有油门签名节流::事件ta - >诠释 - >事件ta ...

PS:我是非常新手哈斯克尔所以代码可能可以更多更紧凑或优雅。

{----------------------------------------------------------------------------- 

------------------------------------------------------------------------------} 
{-# LANGUAGE ScopedTypeVariables #-} -- allows "forall t. NetworkDescription t" 

import Graphics.UI.WX hiding (Event) 
import Reactive.Banana 
import Reactive.Banana.WX 
import Data.Time 

{----------------------------------------------------------------------------- 
    Main 
------------------------------------------------------------------------------} 

data ThrottledValue a = FireStoredValue a | FireNowAndStartTimer a| HoldIt a | Stopped deriving Show 
data ThrottledEvent a = TimerEvent | RealEvent a deriving Show 

main = start $ do 
    f <- frame [text := "Countercesss"] 
    sl1 <- hslider f False 0 100 [] 
    sl2 <- hslider f False 0 100 [] 
    set f [ layout := column 0 [widget sl1, widget sl2] ] 
    t <- timer f [] 
    set t [ enabled := False ] 
    let networkDescription :: forall t. NetworkDescription t() 
     networkDescription = do 
     slEv <- event0 sl1 command 
     tick <- event0 t command 
     slB <- behavior sl1 selection 
     let (throttledEv, reactimates) = throttle (slB <@ slEv) tick t 100 
     reactimates 
     reactimate $ fmap (\x -> set sl2 [selection := x]) throttledEv  
    net <- compile networkDescription 
    actuate net    

throttle::Event t a -> Event t() -> Timer -> Int -> (Event t a, NetworkDescription t())  
throttle ev tick timer dt = (throttledEv, reactimates) 
     where 
       all = union (fmap (\x-> RealEvent x) ev) (fmap (\x -> TimerEvent) tick) 
       result = accumE Stopped $ fmap h all 
         where 
         h (RealEvent x) Stopped = FireNowAndStartTimer x 
         h TimerEvent Stopped = Stopped 
         h (RealEvent x) (FireNowAndStartTimer _) = HoldIt x 
         h TimerEvent (FireNowAndStartTimer _) = Stopped 
         h (RealEvent x) (HoldIt _) = HoldIt x 
         h (TimerEvent) (HoldIt y) = FireStoredValue y 
         h (RealEvent x) (FireStoredValue _) = HoldIt x 
         h (TimerEvent) (FireStoredValue _) = Stopped   
       start (FireStoredValue a) = Just $ resetTimer timer dt 
       start (FireNowAndStartTimer a) = Just $ resetTimer timer dt 
       start _ = Nothing 
       stop Stopped = Just $ stopTimer timer 
       stop _ = Nothing 
       reactimates = do 
         reactimate $ filterJust $ fmap stop result 
         reactimate $ filterJust $ fmap start result 
       filterFired (FireStoredValue a) = Just a 
       filterFired (FireNowAndStartTimer a) = Just a 
       filterFired _ = Nothing 
       throttledEv = filterJust $ fmap filterFired result     

startTimer t dt = set t [ enabled := True, interval := dt ] 
stopTimer t = set t [ enabled := False ] 
resetTimer t dt = stopTimer t >> startTimer t dt 
+1

如果您对IO不满意,您可以将计时器实现为侦听包含消息的事件(“start”,“stop”,“reset”)并返回另一个事件。一般来说,我建议将使用'reactimate'的函数放入'NetworkDescription' monad中,即'throttle :: ... - > NetworkDescription t(Event ta)',而不是'throttle :: .. - >(事件ta,NetworkDescription t())'。 –

+0

好吧,这使得它确实更清洁,并且在语法方面与使用throttle :: Event t a - > Int - > Event t a(只是使用< - 而不是在do语句中放入)没有多大区别。我已用您的建议重新实施:https://gist.github.com/2905841。我觉得我对这个解决方案很满意。 –

3

从反应式香蕉-0.6开始,绝对有可能实现您想要的功能,但它有一点涉及。

基本上,您已经使用像wxHaskell这样的外部框架来创建计时器,然后您可以使用该计时器来计划事件。 Wave.hs示例演示了如何做到这一点。

目前,我选择在反应香蕉图书馆本身不包含时间概念。原因很简单,即不同的外部框架具有不同分辨率或质量的定时器,没有适合所有情况的单一尺寸。

我的确打算为库本身添加处理时间和定时器的通用帮助函数,但我仍然需要找到一种很好的方法来使它在不同的计时器上具有通用性,并找出我可以提供的保证。