香蕉节流活动
我想对反应性香蕉实施某种类型的事件限制。 它应该起作用,以使得如果从最后一次通过的事件到达的时间少于三秒,事件就不会通过。 如果它没有通过,那么它将被存储并在最后一次触发事件的增量秒后触发。
以下是一个实现此功能的程序,用于列出带时间戳的数字。 将它翻译成反应香蕉是否可能?
另外,在反应式香蕉中,如何在某些其他事件进入后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), [] )
从反应式香蕉-0.6开始,绝对有可能实现你所期望的功能,但它有一点涉及。
基本上,你已经使用像wxHaskell这样的外部框架来创建一个计时器,然后你可以使用它来安排事件。 Wave.hs示例演示了如何做到这一点。
目前,我选择在反应香蕉图书馆本身不包含时间概念。 原因很简单,即不同的外部框架具有不同分辨率或质量的定时器,没有适合所有情况的单一尺寸。
我打算为图书馆本身添加处理时间和计时器的通用帮助函数,但我仍然需要找到一种很好的方法,使其在不同计时器上具有通用性,并找出我可以提供的保证。
好的,我设法实现了我在我的问题中描述的内容。 我不是很高兴IO需要通过反应来控制计时器。 我想知道是否有可能用节气门标记油门:: Event ta - > Int - > Event ta ...
ps:我是Haskell的新手,所以代码可能更紧凑或更优雅。
{-----------------------------------------------------------------------------
------------------------------------------------------------------------------}
{-# 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
链接地址: http://www.djcxy.com/p/60079.html