[reactive] FRP, continuous time and concurrency

Freddie Manners f.manners at gmail.com
Wed Jun 10 17:26:02 EDT 2009


This is a silly example.  Console lines "b = x" update the value of b; "c =
y" likewise; lines starting "a" cause the current value of a to be printed.

module Main
   where

import FRP.Reactive
import FRP.Reactive.LegacyAdapters
import Data.List
import Control.Monad
import Control.Concurrent
import Control.Applicative

parseEvent :: String -> Event String -> Event Integer
parseEvent s = fmap read . joinMaybes . fmap (stripPrefix s)

main :: IO ()
main = do
      cl    <- makeClock
      (s,e) <- makeEvent cl
      forkIO . forever $ getLine >>= s
      let b = stepper 0 $ parseEvent "b =" e
      let c = stepper 0 $ parseEvent "c =" e
      let p = parseEvent "a" e
      let a = liftA2 (+) b c -- the only interesting line

      adaptE . fmap print $ snapshot_ a p

So yes, this does use explicit concurrency because "feeding" the reactive
events (with getLine) and printing the answers must happen in different
threads.

Interestingly, this fairly simple program gobbles CPU and RAM on
reactive-0.11, as well as running with a bit of a lag.  Could joinMaybes be
to blame?  I don't know how happy the Monad instance of Event is these days.

Freddie

2009/6/10 Álvaro García Pérez <agarcia at babel.ls.fi.upm.es>

> I don't completely understand how can you wrap your reactive definition
> into a particular implementation.
>
> Let's take the IO legacy adapter for example, how could I use the
> applicative lifting (liftA2) with behaviours to implement things inside the
> IO monad? Can you give some code adapting the "a = liftA2 (+) b c" example
> to the console? Are threads and concurrency required to do so?
>
> Alvaro.
>
> 2009/6/10 Freddie Manners <f.manners at gmail.com>
>
> So, it may be that we've made Num a => Behavior a an instance of Num in
>> which case this is valid code; I think the definition
>>
>> a = liftA2 (+) b c
>>
>> is more instructive.  The point is that Behavior is an instance of
>> Applicative, so we can apply a time-varying function (such as (+) b) to a
>> time-varying argument (such as c) so that the answer is modified when either
>> the function or the argument is.
>>
>> Freddie
>>
>> 2009/6/10 Patai Gergely <patai_gergely at fastmail.fm>
>>
>>  > Anyway, can you give any implementation of this example using the
>>> > reactive library?
>>> If b and c are signals (or behaviours as they are called in Reactive)
>>> carrying Num values of the same type, you can simply say a = b + c, and
>>> you're done. Signal a will be updated only when either b or c is
>>> updated. Note that this must be understood in the context of laziness,
>>> i.e. not a single sum is calculated until a sample of a is requested.
>>>
>>> Gergely
>>>
>>> --
>>> http://www.fastmail.fm - One of many happy users:
>>>  http://www.fastmail.fm/docs/quotes.html
>>>
>>> _______________________________________________
>>> Reactive mailing list
>>> Reactive at haskell.org
>>> http://www.haskell.org/mailman/listinfo/reactive
>>>
>>
>>
>> _______________________________________________
>> Reactive mailing list
>> Reactive at haskell.org
>> http://www.haskell.org/mailman/listinfo/reactive
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/reactive/attachments/20090610/8fd7255e/attachment.html


More information about the Reactive mailing list