Functional Banana Traveller - Input Handling

こ雲淡風輕ζ 提交于 2019-12-25 03:26:33

问题


This is a sub-problem from my Traveller project.

I've put together the rudementary code that will handle input. It works, until I introduce a TChan to the mix. Below is the working code, with an example of how to use it. Then, I will change it and explain why I am doing so. Then, I'll talk about the problem.

{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad (forever)
import Control.Concurrent (forkIO)
import Control.Monad.STM (STM,atomically)
import Control.Concurrent.STM.TChan
import Reactive.Banana
import Reactive.Banana.Frameworks


data Planet = Vulcan
            | Mars
            | Terra
                deriving (Eq,Read,Show)

data Command = Move Planet
             | Look
             | Quit
             | Null
                deriving Show

makeNetworkDescription :: AddHandler (Maybe Command) -> IO EventNetwork
makeNetworkDescription addCommandEvent = compile $ do
   eInput <- fromAddHandler addCommandEvent
   let eCommand = filterJust eInput 
       bCommand = stepper Null eCommand 
   eCommandChanged <- changes bCommand

reactimate $ (\n -> appendFile "output.txt" ("Command is " ++ show n)) <$>  
eCommandChanged

Executing the following in ghci will demonstrate that this works.

(addCommandEvent,fireCommand) <- newAddHandler :: IO (AddHandler (Maybe Command),Maybe Command -> IO ())
networkDescr <- makeNetworkDescription addCommandEvent
actuate networkDescr
return (Just $ Look) >>= fireCommand

So, now I have have the basic mechanism in place, I want to start building it out. This is going to be a multiplayer game. The first step in addressing this as far the the input handling goes is getting input from a TChan. The idea being, all players will write to this TChan, and each command will be processed in the order it arrived.

So I added a new function 'inputFrame'

inputFrame :: TChan Command -> IO ()
inputFrame commandChannel = do
   (addCommandEvent,fireCommand) <- newAddHandler
   networkDescr <- makeNetworkDescription addCommandEvent
   actuate networkDescr
   forkIO $ forever (atomically $ tryReadTChan commandChannel) >>= fireCommand
   return ()

Here is how I attempt to use it, in ghci.

commandChan <- atomically $ newTChan :: IO (TChan Command)
_ <- atomically $ writeTChan commandChan Look

output.txt doesn't get written to. commandChan is being read, as I check to see if it becomes empty after populating it. Is it obvious what I'm doing wrong? If not, how may I go about troubleshooting the problem? Also, for my intended purposes, is a TChan the right choice?


回答1:


You probably wanted

forkIO $ forever (atomically (tryReadTChan commandChannel) >>= fireCommand)

but I haven't tested this. Also, at a guess, you probably will want to avoid tryReadTChan here. Just use plain old readTChan, so that you get the efficient retry instead of polling.



来源:https://stackoverflow.com/questions/12919136/functional-banana-traveller-input-handling

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!