
A 05/05/2012, às 08:40, Heinrich Apfelmus escreveu:
Miguel Negrao wrote:
One other question, is it possible in reactive-banana to define “recursive” event streams. For instance consider a stream which receives numbers between 0.0 and 1.0. If the last outputted value was between 0.8 an 1.0 then output 1-x otherwise output x. After that it only leta numbers through if they are between 0.0 and 0.2 or between 0.8 and 1.0.
The standard way to do recursion in reactive-banana is to use multiple recursion between a Behavior and an Event . See also
ok, I will study that.
Note that the specification you gave does not require recursion, though. Here an implementation of your example.
import Reactive.Banana
example :: Event t Double -> Event t Double example e = filterJust e2 where e2 = f <$> bIsFirst <@> e
bIsFirst = stepper True $ False <$ e
between x a b = a < x && x < b
f True x | between x 0.8 1.0 = Just $ 1 - x | otherwise = Just $ x f False x | between x 0.8 1.0 = Just $ x | between x 0.0 0.2 = Just $ x | otherwise = Nothing
Here an example output
GHCi> interpretModel example [[0.9],[0.3],[0.4]] [[9.999999999999998e-2],[],[]]
Hum, that’s not exactly what I wanted. So if it’s the first event just let it through, and then filter it. If it’s not the first event, then do the inversion (1-x) or not depending on the last outputted value, and then filter it. An input of [[0.9],[0.5],[0.1],[0.9],[0.9]] should produce [[0.9],[],[0.9],[0.1],[0.9]] The following code is not correct but it’s closer to what I described: module Main where import Reactive.Banana main :: IO() main = do list <- interpretModel example [[0.9],[0.3],[0.4],[0.15],[0.87]] putStrLn $ show list example :: Event t Double -> Event t Double example e = filterede2 where filterede2 = filterE (\x->between x 0.0 0.2 && between x 0.8 1.0) e2 e2 = f <$> bIsFirst <@> e <@> e2 bIsFirst = stepper True $ False <$ e between x a b = a < x && x < b f True x y = x f False x y | between y 0.8 1.0 = 1 - x | otherwise = x best, Miguel