Reactive Banana: Bindings - haskell

I am working on a small terminal-based UI and I want to use Reactive Banana for describing interactions. The only external event I am interested in, is whether the user has pressed a key.
From what I gathered from the Frameworks documentation, I can either use polling to get the state of the terminal input buffer or pass an "event handler" to Reactive Banana. I'd rather prefer the latter, but I find the event handling section confusing. How exactly would I describe an event-driven version of getChar? In the end, I'd like to operate on an "Event Key" stream.
I have looked at the SDL and wx bindings, but I don't find them of much help, since they are littered with library related idiosyncracies, and I'd much appreciate a more concise explanation how event handlers, event loops and Reactive Banana mix together.

As it turns out, dealing with external events is remarkably flexible and simple with Reactive Banana. All that is needed is to create an event handler with "newAddHandler" which consists of two pieces, an "AddHandler" from which events can be created using the reactimate function, and a Handler which has to be invoked by the glue code (binding) that bridges Reactive Banana to the framework (in my case, I just feed the result of getChar to the handler).
Here is an example code that echos keystrokes:
echo = do
(keyEventHandler, fire) <- newAddHandler
-- Network Specification (echo keyboard input)
let networkDescription =
fromAddHandler keyEventHandler >>= -- Create event stream from handler
reactimate . fmap print -- Map print over event stream
compile networkDescription >>= actuate
-- Event Loop
hSetBuffering stdin NoBuffering
forever $ do
ready <- hReady stdin
if ready
then getChar >>= fire -- Create keyboad event
else return ()
The nice thing about reactive banana is that the callback function "fire" can be invoked from any context. Thus, the event loop could as well run in a thread or be invoked from a C library. More about this can be found by Heinrich's answer to How to implement a game loop in reactive-banana?.
However, catching arbitrary keyboard input events without polling is not as easy as I thought, POSIX won't allow it (if I am not mistaken) and even if it did the code would not be portable.
Also note that on Windows machines, you have to hit enter, I still have to find a way around that problem. More on this issue is found at the Haskell bugtracker

Related

Why does changing my FRP implementation to be more reactive lag?

I got a version of snake working with the threepenny-gui library, but I didn't like the fact that I was explicitly calling newEvent and addStateUpdate manually instead of defining the behavior completely based on events, e.g. this:
(updates, addUpdate) <- liftIO newEvent
managerB <- accumB initialManager updates
on UI.tick timer $ \_ -> addUpdate $ \manager -> manager'
compared to:
managerB <- accumB initialManager $
UI.tick timer $> \manager -> manager'
IIUC the second is more idiomatic FRP, as it defines a behavior with the actual event instead of creating a proxy event to proxy updates through. But when I make this change, it causes one of two problems:
If I define managerB first (using RecursiveDo to access timer, which is defined below), nothing's rendered at all
If I move managerB to the end (using RecursiveDo to access managerB from the DOM elements), the initial movement when hitting an arrow key for the first time lags, and the frames render in a jerky fashion.
Am I doing something wrong? What's the idiomatic way I should structure these events/behaviors?
Code diff here: https://github.com/brandonchinn178/snake/compare/inline-event-handlers
A not particularly pretty workaround for the jerkiness, which I tested on the alternate branch in your repository, is, so to say, using both approaches at once: re-firing the tick event and using that instead of UI.tick timer to define managerB:
(timeE, fireTime) <- liftIO newEvent
on UI.tick timer $ \_ -> liftIO (fireTime ())
let managerUpdateE =
fmap concatenate . unions $
[ timeE $> getNextManagerState
-- Instead of: UI.tick timer $> getNextManagerState
-- etc.
The issue appears to be that plugging UI.tick timer directly into the event network somehow gets in the way of Threepenny sending the JavaScript calls needed to update the UI in a timely way. The indirection in using on with fireTime (which, in particular, should mean timeE happens notionally after UI.tick timer) seems to skirt around the problem. A less intrusive workaround would be, instead of introducing timeE, explicitly calling flushCallBuffer in a handler for UI.tick timer; in my tests, however, that reduced the jerkiness a lot but didn't eliminate it completely. (See also threepenny-gui issue #191 for possibly relevant background information.)
As for the delay on the first keystroke, it appears that can be eliminated by moving your invocation of UI.start timer to the very end of gui, after managerB and the rest of your event network is set up.
(On an additional note, it is probably a good idea to follow the recommendation of the Graphics.UI.Threepenny.Timer docs and set -threaded in the ghc-options for compiling your executable, even if that doesn't seem to have an effect on the problem you describe here.)

Dealing with the current time in reactive-banana

How do you deal with the current time in reactive-banana?
Ideally I'd like to have a Behaviour which I can "poll" to get the current time. However, polling Behaviours with Events (via <# etc.) gives me the value of the Behaviour from the previous Event, not the current value. (I realise this is to avoid cyclic definitions which is indeed useful.)
I found fromPoll which I thought would help. Behaviours that are observed from fromPoll cannot depend on themselves, thus no cycles can be introduced by observing the behaviour just before this Event is fired rather than just after the previous Event fired.
A digression
In somewhat more formal terms I am suggesting that Events always occur at time t+ and Behaviours are always observed at time t- i.e. Events observe behaviours that happen an infinitessimally short time before them. New values of Behaviours generated by accumB and friends would always start from time t+ so could not be observed by Events which also happen at time t+.
Under this proposed semantics Behaviours created by fromPoll would be updated just before each Event is processed. Other Behaviours would be updated afterwards because they are created by accumB and friends.
My use case
Anyway, that's a significant digression to my main question. I want to know if there's some way to deal with current time (not the time of the previous Event) in reactive-banana. My use case is, for example, to keep track of the pings that entities send and if any of them hasn't sent a ping in a particular time interval to signal a warning event.
Of course I can and will fire off events very frequently, so my warnings won't be incorrect by a large amount. However it does seem to be a wart that they cannot be precise.
What's the right way of dealing with this?
Given your example use case, I think you should be fine if you stay away from fromPoll. To explain why, a few clarifications are needed. (Note: in what follows, "stream" refers to an Event t a, and "occurrence" to one of the firings which compose them.)
However, polling Behaviours with Events (via <# etc.) gives me the value of the Behaviour from the previous Event, not the current value.
I suppose you are alluding to explanations such as this one, from the docs for stepper:
Note that the smaller-than-sign in the comparision timex < time means that the value of the behavior changes "slightly after" the event occurrences. This allows for recursive definitions.
That delay, however, is only with respect to the stream used to define the behaviour (i.e. the one you pass to stepper/accumB) and any streams that are synchronised with it. For instance, suppose you have two independent streams, eTick and eTock, and the following network snippet:
eIncrement = (+1) <$ eTick
bCount = accumB 0 eIncrement
eCountTick = bCount <# eTick
eCountTock = bCount <# eTock
eIncrement and eCountTick are in sync with eTick, and so the value observed through eCountTick is the "old" value; that is, the value before the synchronised update. From the point of view given by eCountTock, however, none of that matters. To an observer using eCountTock, there is no delay to speak of, and the value is always the current one.
Behaviours that are observed from fromPoll cannot depend on themselves, thus no cycles can be introduced by observing the behaviour just before this Event is fired rather than just after the previous Event fired.
We are only concerned with streams synchronised with the one which updates the behaviour. Thus, as far as observed values go "just before the next occurrence" and "just after the previous occurrence" boil down to the same thing. fromPoll, however, muddles things quite a bit. It creates a behaviour which is updated whenever any occurrence happens in the event network; and so the updates are synchronised with the union of all streams. There is no such thing as a stream independent from a fromPoll event, and therefore the observed value will be affected by the delay however we observe it. That being so, fromPoll won't work for an application-driving clock, which requires tracking continuous change with some accuracy.
Implicit in all of the above is that reactive-banana has no built-in notion of time. There are only the "logical" time lines within each stream, which can be interwoven by merging streams. So if we want a current time behaviour our best bet is building one from an independent stream. Here is a demo of that approach, which will produce fresh and timely results as far as the precision of threadDelay allows:
{-# LANGUAGE RankNTypes #-}
module Main where
import Control.Concurrent
import Control.Monad
import Data.Time
import Reactive.Banana
import Reactive.Banana.Frameworks
main = do
let netDesc :: forall t. Frameworks t => Moment t ()
netDesc = do
(eTime, fireTime) <- newEvent
liftIO . forkIO . forever $
threadDelay (50 * 1000) >> getCurrentTime >>= fireTime
bTime <- flip stepper eTime <$> liftIO getCurrentTime
(eTick, fireTick) <- newEvent
liftIO . forkIO . forever $
threadDelay (5000 * 1000) >> fireTick ()
reactimate $ print <$> bTime <# eTick
network <- compile netDesc
actuate network >> threadDelay (52000 * 1000) >> pause network
bTime is updated through eTime each 0.05s; it is observed through eTick, a stream independent from eTime with occurrences every 5s. You can then use eTick and streams derived from it to observe and update your entities. Alternatively, you can combine bTime and the entity behaviours in applicative style to get, e.g. behaviours for the latest pings, to be observed with eTick.
Having a canonical time behaviour looks like a sound approach in your case; it is conceptually clear and readily generalisable for multiple ticks. In any case, other approaches that you can play with include getting rid of bTime and using eTick as a low-resolution current time stream (though that seems to make the threadDelay innacurcies build up faster), and getting rid of eTick by using changes to get a stream of freshly updated values from the behaviour (through that comes with its own quirks and annoyances, as the documentation hints at).

Functional Banana Traveller - input Handling : Will this do what I want?

The way I want to manage input for my game is to poll a TChan, and then create an Event when an eTick happens. But will the way I'm trying it work?
data UAC = UAC (AID,PlayerCommand) deriving Show
makeNetworkDescription :: forall t . Frameworks t =>
TChan UAC ->
AddHandler () ->
TChan GameState ->
Moment t ()
makeNetworkDescription commandChannel tickHandler gsChannel = do
eTick <- fromAddHandler tickHandler
bCChannel <- fromPoll $ grabCommands commandChannel
let eCChannel = bCChannel <# eTick
...
reactimate ...
grabCommands :: TChan UAC -> IO [UAC]
grabCommands unval = do
(atomically $ readTChan unval) `untilM` (atomically $ isEmptyTChan unval)
from the documentation for fromPoll
"Input, obtain a Behavior by frequently polling mutable data, like the current time. The resulting Behavior will be updated on whenever the event network processes an input event."
Am I understanding this correctly? The TChan is being populated from other code and then every eTick I empty it and get another Event t [UAC]?
Maybe my understanding is wrong, or this computation is too expensive for fromPoll. In that case what's a better direction to go in?
I was facing the same question in my game. I decided to try to keep the event network as free as possible from implementation-specific stuff (such as input protocols). Instead I block in a IO thread outside of the event network and send processed events to the event network from there (using something like the EventSource "design pattern" used in the reactive-banana examples.
The reason for this is that this way the event network has to process only well-defined and simple input commands and fromPoll is not needed. The particulars (such as if the input is coming from local input or a network, if the input events are well-formed, how errors are handled) are done in other parts of the program.
On the other hand, if the design of your game is such that input is handled only during the game ticks and input events must be buffered, then you will need some place to hold them. A TChan will do the trick as well as any other way, I suppose.

Implement main server loop in Haskell?

What is the generally accepted way to implement the main loop of a server that needs to wait on a heterogeneous set of events? That is the server should wait (not busywait) until one of the following occurs:
new socket connection
data available on an existing socket
OS signal
third-party library callbacks
I think you're thinking in terms of a C paradigm with a single thread, nonblocking I/O, and a select() call.
You can manage to write something like that in Haskell, but Haskell has much more to offer:
lightweight threads
safe and efficient concurrent data primitives like Mvar and Chan
the Big Gun: Software Transactional Memory
I recommend you fork a new thread for every separate point of contact with the outside world, and keep everything coordinated with STM.
Use takeMVar and putMVar to synchronize between threads. They generally block the thread if operation is not permitted.
Read ghc docs.
I'd like to make it clear I think the two solutions posted first are better than this one for the specific problem you have, but here's a way to solve the type of problem you presented.
A simple way round this is to take your definitions like
data SocketConn = ....
data DataAvail = ...
data OSSignal = ...
data Callback = ...
and define the unsimplified version of
data ServerEvent = Sok SocketConn | Dat DataAvail | Sig OSSignal | Call Callback
handleEvent :: ServerEvent -> IO ()
handleEvent (Soc s) = ....
handleEvent (Dat d) = ....
handleEvent (Sig o) = ....
handleEvent (Call c) = ....
Like I say, read up on the other answers!
Software Transactional Memory (STM) is the main way to do a multi-way wait.
However, by the looks of things, in your case you probably just want to spawn a seperate Haskell thread for each task, and let each such thread block while there's nothing happening.
You wouldn't want to create a thousand OS threads, but a thousand Haskell threads is no trouble at all.
(If these threads need to coordinate from time to time, then again, STM is probably the simplest, most reliable way to do that.)

State-dependent event processing with state updates

I want to use FRP (i.e., reactive banana 0.6.0.0) for my project (a GDB/MI front-end). But I have troubles declaring the event network.
There are commands from the GUI and there are stop events from GDB. Both need to be handled and handling them depends on the state of the system.
My current approach looks like this (I think this is the minimum required complexity to show the problem):
data Command = CommandA | CommandB
data Stopped = ReasonA | ReasonB
data State = State {stateExec :: Exec, stateFoo :: Int}
data StateExec = Running | Stopped
create_network :: NetworkDescription t (Command -> IO ())
create_network = do
(eCommand, fCommand) <- newEvent
(eStopped, fStopped) <- newEvent
(eStateUpdate, fStateUpdate) <- newEvent
gdb <- liftIO $ gdb_init fStopped
let
eState = accumE initialState eStateUpdate
bState = stepper initialState eState
reactimate $ (handleCommand gdb fStateUpdate <$> bState) <#> eCommand
reactimate $ (handleStopped gdb fStateUpdate <$> bState) <#> eStopped
return fCommand
handleCommand and handelStopped react on commands and stop events depending on the current state. Possible reactions are calling (synchronous) GDB I/O functions and firing state update events. For example:
handleCommand :: GDB -> ((State -> State) -> IO ()) -> State -> Command -> IO ()
handleCommand gdb fStateUpdate state CommandA = case stateExec state of
Running -> do
gdb_interrupt gdb
fStateUpdate f
where f state' = state' {stateFoo = 23}
The problem is, when f gets evaluated by accumE, state' sometimes is different from state.
I am not 100% sure why this can happen as I don't fully understand the semantics of time and simultaneity and the order of "reactimation" in reactive banana. But I guess that state update functions fired by handleStopped might get evaluated before f thus changing the state.
Anyway, this event network leads to inconsistent state because the assumptions of f on the "current" state are sometimes wrong.
I have been trying to solve this problem for over a week now and I just cannot figure it out. Any help is much appreciated.
It looks like you want to make a eStateUpdate event occur whenever eStop or eCommand occurs?
If so, you can simply express it as the union of the two events:
let
eStateUpdate = union (handleCommand' <$> eCommand)
(handleStopped' <$> eStopped)
handleCommand' :: Command -> (State -> State)
handleStopped' :: Stopped -> (State -> State)
eState = accumE initialState eStateUpdate
etc.
Remember: events behave like ordinary values which you can combine to make new ones, you're not writing a chain of callback functions.
The newEvent function should only be used if you want to import an event from the outside world. That's the case for eCommand and eStopped, as they are triggered by the external GDB, but the eStateUpdate event seems to be internal to the network.
Concerning behavior of your current code, reactive-banana always does the following things when receiving an external event:
Calculate/update all event occurrences and behavior values.
Run the reactimates in order.
But it may well happen happen that step 2 triggers the network again (for instance via the fStateUpdate function), in which case the network calculates new values and calls the reactimates again, as part of this function call. After this, flow control returns to the first sequence of reactimates that is still being run, and a second call to fStateUpdate will have strange effects: the behaviors inside the network have been updated already, but the argument to this call is still an old value. Something like this:
reactimate1
reactimate2
fStateUpdate -- behaviors inside network get new values
reactimate1'
reactimate2'
reactimate3 -- may contain old values from first run!
Apparently, this is tricky to explain and tricky to reason about, but fortunately unnecessary if you stick to the guidelines above.
In a sense, the latter part embodies the trickiness of writing event handlers in the traditional style, whereas the former part embodies the (relative) simplicity of programming with events in FRP-style.
The golden rule is:
Do not call another event handler while handling an event.
You don't have to follow this rule, and it can be useful at times; but things will become complicated if you do that.
As far as I can see, FRP seems not to be the right abstraction for my problem.
So I switched to actors with messages of type State -> IO State.
This gives me the required serialization of events and the possibility to do IO when updating the state. What I loose is the nice description of the event network. But it's not too bad with actors either.

Resources