haskellreactive-programmingfrpreactive-banana

Reactive Banana: consume parametrized call to an external API


Starting from a previous question here: Reactive Banana: how to use values from a remote API and merge them in the event stream

I have a bit different problem now: How can I use the Behaviour output as input for an IO operation and finally display the IO operation's result?

Below is the code from the previous answer changed with a second output:

import System.Random

type RemoteValue = Int

-- generate a random value within [0, 10)
getRemoteApiValue :: IO RemoteValue
getRemoteApiValue = (`mod` 10) <$> randomIO

getAnotherRemoteApiValue :: AppState -> IO RemoteValue
getAnotherRemoteApiValue state = (`mod` 10) <$> randomIO + count state

data AppState = AppState { count :: Int } deriving Show

transformState :: RemoteValue -> AppState -> AppState
transformState v (AppState x) = AppState $ x + v

main :: IO ()
main = start $ do
    f        <- frame [text := "AppState"]
    myButton <- button f [text := "Go"]
    output   <- staticText f []
    output2  <- staticText f []

    set f [layout := minsize (sz 300 200)
                   $ margin 10
                   $ column 5 [widget myButton, widget output, widget output2]]

    let networkDescription :: forall t. Frameworks t => Moment t ()
        networkDescription = do    
          ebt <- event0 myButton command

          remoteValueB <- fromPoll getRemoteApiValue
          myRemoteValue <- changes remoteValueB

          let
            events = transformState <$> remoteValueB <@ ebt

            coreOfTheApp :: Behavior t AppState
            coreOfTheApp = accumB (AppState 0) events

          sink output [text :== show <$> coreOfTheApp] 

          sink output2 [text :== show <$> reactimate ( getAnotherRemoteApiValue <@> coreOfTheApp)] 

    network <- compile networkDescription    
    actuate network

As you can see what I am trying to do it is using the new state of the application -> getAnotherRemoteApiValue -> show. But it doesn't work.

Is actually possible doing that?

UPDATE Based on the Erik Allik and Heinrich Apfelmus below answers I have the current code situation - that works :) :

{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import System.Random
import Graphics.UI.WX hiding (Event, newEvent)
import Reactive.Banana
import Reactive.Banana.WX


data AppState = AppState { count :: Int } deriving Show

initialState :: AppState
initialState = AppState 0

transformState :: RemoteValue -> AppState -> AppState
transformState v (AppState x) = AppState $ x + v

type RemoteValue = Int

main :: IO ()
main = start $ do
    f        <- frame [text := "AppState"]
    myButton <- button f [text := "Go"]
    output1  <- staticText f []
    output2  <- staticText f []

    set f [layout := minsize (sz 300 200)
                   $ margin 10
                   $ column 5 [widget myButton, widget output1, widget output2]]

    let networkDescription :: forall t. Frameworks t => Moment t ()
        networkDescription = do    
          ebt <- event0 myButton command

          remoteValue1B <- fromPoll getRemoteApiValue

          let remoteValue1E = remoteValue1B <@ ebt

              appStateE = accumE initialState $ transformState <$> remoteValue1E
              appStateB = stepper initialState appStateE

              mapIO' :: (a -> IO b) -> Event t a -> Moment t (Event t b)
              mapIO' ioFunc e1 = do
                  (e2, handler) <- newEvent
                  reactimate $ (\a -> ioFunc a >>= handler) <$> e1
                  return e2

          remoteValue2E <- mapIO' getAnotherRemoteApiValue appStateE

          let remoteValue2B = stepper Nothing $ Just <$> remoteValue2E

          sink output1 [text :== show <$> appStateB] 
          sink output2 [text :== show <$> remoteValue2B] 

    network <- compile networkDescription    
    actuate network

getRemoteApiValue :: IO RemoteValue
getRemoteApiValue = do
  putStrLn "getRemoteApiValue"
  (`mod` 10) <$> randomIO

getAnotherRemoteApiValue :: AppState -> IO RemoteValue
getAnotherRemoteApiValue state = do
  putStrLn $ "getAnotherRemoteApiValue: state = " ++ show state
  return $ count state

Solution

  • The fundamental problem is a conceptual one: FRP Events and Behaviors can only be combined in a pure way. In principle, it is not possible to have a function of type, say

    mapIO' :: (a -> IO b) -> Event a -> Event b
    

    because the order in which the corresponding IO actions are to be executed is undefined.


    In practice, it may sometimes be useful to perform IO while combining Events and Behaviors. The execute combinator can do this, as @ErikAllik indicates. Depending on the nature of getAnotherRemoteApiValue, this may be the right thing to do, in particular if this is function is idempotent, or does a quick lookup from location in RAM.

    However, if the computation is more involved, then it is probably better to use reactimate to perform the IO computation. Using newEvent to create an AddHandler, we can give an implementation of the mapIO' function:

    mapIO' :: (a -> IO b) -> Event a -> MomentIO (Event b)
    mapIO' f e1 = do
        (e2, handler) <- newEvent
        reactimate $ (\a -> f a >>= handler) <$> e1
        return e2
    

    The key difference to the pure combinator

    fmap :: (a -> b) -> Event a -> Event b
    

    is that the latter guarantees that the input and result events occur simultaneously, while the former gives absolutely no guarantee about when the result event occurs in relation to other events in the network.

    Note that execute also guarantees that input and result are have simultaneous occurrences, but places informal restrictions on the IO allowed.


    With this trick of combining reactimate with newEvent a similar combinator can be written for Behaviors in a similar fashion. Keep in mind that the toolbox from Reactive.Banana.Frameworks is only appropriate if you are dealing with IO actions whose precise order will necessarily be undefined.


    (To keep this answer current, I have used the type signatures from the upcoming reactive-banana 1.0. In version 0.9, the type signature for mapIO' is

    mapIO' :: Frameworks t => (a -> IO b) -> Event t a -> Moment t (Event t b)
    

    )