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

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.

Related

Reactive Banana: Bindings

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

TMVar, but without the buffer?

I'm trying to do communication between Haskell lightweight threads. Threads want to send each other messages for communication and synchronisation.
I was originally using TMVar for this, but I've just realised that the semantics are wrong: a TMVar will store one message in it internally, so positing a message to an empty TMVar won't block. It'll only block if you post a message to a full TMVar.
Can anyone suggest a similar STM IPC construct which:
will cause all writes to block until the message is consumed;
will cause all reads to block until a message is provided?
i.e. a zero-length pipe would be ideal; but I don't think BoundedChan would be happy if I gave it a capacity of 0. (Also, it's not STM.)
If I understand your problem correctly, I don't think you can, since the transactional guarantees mean that transaction A can't read from transaction B's write until transaction B is committed, at which point it can no longer block.
TMVar is the closest you're going to get if you're using STM. With IO, you may be able to build a structure which only completes a write when a reader is available (this structure may already exist, but I'm not aware of it).
I'd suggest to reformulate the two requirements:
will cause all writes to block until the message is consumed;
will cause all reads to block until a message is provided.
The problem is with terms block and consumed/provided. With STM there is no notion of block, there is just retry, which has a different semantics: It restarts the current transaction - it doesn't wait until something happens (this could cause deadlocks). So we can't say "block until ...", we can only say something like "the transaction succeeds only when ...".
Similarly, what does "until a message is consumed/provided" mean? Since transactions are atomic, it can only be "until the transaction that consumed/provided a message succeeded".
So let's try to reformulate:
will cause all writes to retry until a transaction that consumes the message succeeds;
will cause all reads to retry until a transaction that provides a message succeeds.
But now the first point doesn't make sense: If a write retries, there is no message to be consumed, the transaction didn't pause, it's been discarded and started over - possibly producing a different message!
In other words: Any data can ever leave a STM transaction only when it succeeds (completes). This is by design - the transactions are always atomic from the point of view of the outside world / other transactions - you can never observe results of only a part of a transaction. You can never observe two transactions interacting.
So a 0-length queue is a bad analogy - it will never allow to pass any data though. At the end of any transaction, it'll have to have to be empty, so no data will ever pass through.
Nevertheless I believe it'll be possible to reformulate the requirements according to your goals and subsequently find a solution.
You say you would be happy with one side or the other being in IO rather than STM. So then it is not too hard to code this up. Let's start with the version that has receiving in IO. To make this happen, the receiver will have to initiate the handshake.
type SynchronousVar a = TChan (TMVar a)
send :: SynchronousVar a -> a -> STM a
receive :: SynchronousVar a -> IO a
send svar a = do
tmvar <- readTChan svar
putTMVar tmvar a
receive svar = do
tmvar <- newEmptyTMVarIO
atomically $ writeTChan svar tmvar
atomically $ takeTMVar tmvar
A similar protocol can be written that has sending start the handshake.
type SynchronousVar a = TChan (a, TMVar ())
send :: SynchronousVar a -> a -> IO a
receive :: SynchronousVar a -> STM a
send svar a = do
tmvar <- newEmptyTMVarIO
atomically $ writeTChan svar (a, tmvar)
atomically $ takeTMVar tmvar
receive svar = do
(a, tmvar) <- readTChan svar
putTMvar tmvar ()
return a
Probably, if you really need synchronous communication, this is because you want two-way communication (i.e. the action that's running in IO wants to know something about the thread it's synchronizing with). It is not hard to extend the above protocol to pass off a tad more information about the synchronization (by adding it to the one-tuple in the former case or to the TMVar in the latter case).

Concurrency considerations between pipes and non-pipes code

I'm in the process of wrapping a C library for some encoding in a pipes interface, but I've hit upon some design decisions that need to be made.
After the C library is set up, we hold on to an encoder context. With this, we can either encode, or change some parameters (let's call the Haskell interface to this last function tune :: Context -> Int -> IO ()). There are two parts to my question:
The encoding part is easily wrapped up in a Pipe Foo Bar IO (), but I would also like to expose tune. Since simultaneous use of the encoding context must be lock protected, I would need to take a lock at every iteration in the pipe, and protect tune with taking the same lock. But now I feel I'm forcing hidden locks on the user. Am I barking up the wrong tree here? How is this kind of situation normally resolved in the pipes ecosystem? In my case I expect the pipe that my specific code is part of to always run in its own thread, with tuning happening concurrently, but I don't want to force this point of view upon any users. Other packages in the pipes ecosystem do not seem to force their users like either.
An encoding context that is no longer used needs to be properly de-initialized. How does one, in the pipes ecosystem, ensure that such things (in this case performing som IO actions) are taken care of when the pipe is destroyed?
A concrete example would be wrapping a compression library, in which case the above can be:
The compression strength is tunable. We set up the pipe and it runs along merrily. How should one best go about allowing the compression strength setting to be changed while the pipe keeps running, assuming that concurrent access to the compression codec context must be serialized?
The compression library allocated a bunch of memory off the Haskell heap when set up, and we'll need to call some library function to clean this up when the pipe is torn down.
Thanks… this might all be obvious, but I'm quite new to the pipes ecosystem.
Edit: Reading this after posting, I'm quite sure it's the vaguest question I've ever asked here. Ugh! Sorry ;-)
Regarding (1), the general solution is to change your Pipe's type to:
Pipe (Either (Context, Int) Foo) Bar IO ()
In other words, it accepts both Foo inputs and tune requests, which it processes internally.
So let's then assume that you have two concurrent Producers corresponding to inputs and tune requests:
producer1 :: Producer Foo IO ()
producer2 :: Producer (Context, Int) IO ()
You can use pipes-concurrency to create a buffer that they both feed into, like this:
example = do
(output, input) <- spawn Unbounded
-- input :: Input (Either (Context, Int) Foo)
-- output :: Output (Either (Context, Int) Foo)
let io1 = runEffect $ producer1 >-> Pipes.Prelude.map Right >-> toOutput output
io2 = runEffect $ producer2 >-> Pipes.Prelude.map Left >-> toOutput output
as <- mapM async [io1, io2]
runEffect (fromInput >-> yourPipe >-> someConsumer)
mapM_ wait as
You can learn more about the pipes-concurrency library by reading this tutorial.
By forcing all tune requests to go through the same single-threaded Pipe you can ensure that you don't accidentally have two concurrent invocations of the tune function.
Regarding (2) there are two ways you can acquire a resource using pipes. The more sophisticated approach is to use the pipes-safe library, which provides a bracket function that you can use within a Pipe, but that is probably overkill for your purpose and only exists for acquiring and releasing multiple resources over the lifetime of a pipe. A simpler solution is just to use the following with idiom to acquire the pipe:
withEncoder :: (Pipe Foo Bar IO () -> IO r) -> IO r
withEncoder k = bracket acquire release $ \resource -> do
k (createPipeFromResource resource)
Then a user would just write:
withEncoder $ \yourPipe -> do
runEffect (someProducer >-> yourPipe >-> someConsumer)
You can optionally use the managed package, which simplifies the types a bit and makes it easier to acquire multiple resources. You can learn more about it from reading this blog post of mine.

Ensure IO computations are run in a specific thread

I need to make sure that some actions are run on a specific OS thread. I wrote an API where this thread runs a loop listening to a TQueue and executes the given commands. From the API user side, there is an opaque value that is really just a newtype over this queue.
One problem is that what I really need is to embed arbitrary actions (type IO a), but I believe I can't directly exchange messages of that type. So I currently have something like this (pseudo code) :
makeSafe :: RubyInterpreter -> IO a -> IO (Either RubyError a)
makeSafe (RubyInterpreter q) a = do
mv <- newEmptyTMVarIO
-- embedded is of type IO (), letting me send this in my queue
let embedded = handleErrors a >>= atomically . putTMVar mv
atomically (writeTQueue q (SomeMessage embedded))
atomically (readTMVar mv)
(for more details, this is for the hruby package)
edit - clarifications :
Being able to send actions of type IO a would be nicer, but is not my main objective.
My main problem is that you can shoot yourself in the foot with this API, for example if there is a makeSafe call in the IO action that is passed as a parameter, this will hang.
My secondary problem is that this solution feels a bit contrived, and I wondered if there was a nicer/safer solution around.

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