Sampling a behaviour from outside network

165 views Asked by At

Since sodium has been deprecated by the author I'm trying to port my code to reactive-banana. However, there seem to be some incongruencies between the two that I'm having a hard time overcomming.

For example, in sodium it was easy to retrieve the current value of a behaviour:

retrieve :: Behaviour a -> IO a
retrieve b = sync $ sample b

I don't see how to do this in reactive-banana

(The reason I want this is because I'm trying to export the behaviour as a dbus property. Properties can be queried from other dbus clients)

Edit: Replaced the word "poll" as it was misleading

3

There are 3 answers

0
Philonous On BEST ANSWER

The answer seems to be "it's sort of possible".

sample corresponds to valueB, but there is no direct equivalent to sync.

However, it can be re-implemented with the help of execute:

module Sync where

import Control.Monad.Trans
import Data.IORef
import Reactive.Banana
import Reactive.Banana.Frameworks

data Network = Network { eventNetwork :: EventNetwork
                       , run :: MomentIO () -> IO ()
                       }

newNet :: IO Network
newNet = do
    -- Create a new Event to handle MomentIO actions to be executed
    (ah, call) <- newAddHandler
    network <- compile $ do
        globalExecuteEV <- fromAddHandler ah
        -- Set it up so it executes MomentIO actions passed to it
        _ <- execute globalExecuteEV
        return ()
    actuate network
    return $ Network { eventNetwork = network
                     , run = call -- IO Action to fire the event
                     }

-- To run a MomentIO action within the context of the network, pass it to the
-- event.
sync :: Network -> MomentIO a -> IO a
sync Network{run = call} f = do
    -- To retrieve the result of the action we set up an IORef
    ref <- newIORef (error "Network hasn't written result to ref")
    -- (`call' passes the do-block to the event)
    call $ do
        res <- f
        -- Put the result into the IORef
        liftIO $ writeIORef ref res
    -- and read it back once the event has finished firing
    readIORef ref

-- Example
main :: IO ()
main = do
    net <- newNet -- Create an empty network
    (bhv1, set1) <- sync net $ newBehavior (0 :: Integer)
    (bhv2, set2) <- sync net $ newBehavior (0 :: Integer)
    set1 3
    set2 7
    let sumB = (liftA2 (+) bhv1 bhv2)
    print =<< sync net (valueB sumB)
    set1 5
    print =<< sync net (valueB sumB)
    return ()
4
Erik Kaplun On

For conceptual/architectural reasons, Reactive Banana has functions from Event to Behavior, but not vice versa, and it makes sense too, given th nature and meaning of FRP. I'm quite sure you can write a polling function, but instead you should consider changing the underlying code to expose events instead.

Is there a reason you can't change your Behavior into an Event? If not, that would be a good way to go about resolving your issue. (It might in theory even reveal a design shortcoming you have been overlooking so far.)

1
Ben On

If you have a Behaviour modelling the value of your property, and you have an Event modelling the incoming requests for the property's value, then you can just use (<@) :: Behavior b -> Event a -> Event b1 to get a new event occurring at the times of your incoming requests with the value the property has at that time). Then you can transform that into the actual IO actions you need to take to reply to the request and use reactimate as usual.


1 https://hackage.haskell.org/package/reactive-banana-1.1.0.0/docs/Reactive-Banana-Combinators.html#v:-60--64-