implement proper non-blocking socket handling

This commit is contained in:
nek0 2023-12-10 06:57:48 +01:00
parent 822a2178b4
commit cda2ffaed4
5 changed files with 105 additions and 40 deletions

View file

@ -2,6 +2,8 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import qualified Control.Concurrent.STM as STM
import Control.Monad.RWS.Strict import Control.Monad.RWS.Strict
import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Char8 as B8
@ -16,7 +18,6 @@ import Network.Socket as Net
import Options.Applicative import Options.Applicative
-- internal imports -- internal imports
import Library.Types import Library.Types
@ -39,8 +40,6 @@ main = do
) )
Right (Settings {..}) -> do Right (Settings {..}) -> do
sock <- bindSocket setSocketPath sock <- bindSocket setSocketPath
terminateSocketOnSigint sock
-- Net.listen sock 1024
putStrLn "Bound and listening to socket:" putStrLn "Bound and listening to socket:"
print =<< getSocketName sock print =<< getSocketName sock
putStrLn "-----------------------------------------------------------------------------------" putStrLn "-----------------------------------------------------------------------------------"
@ -50,9 +49,17 @@ main = do
putStrLn "-----------------------------------------------------------------------------------" putStrLn "-----------------------------------------------------------------------------------"
putStrLn "starting game…" putStrLn "starting game…"
now <- getCurrentTime now <- getCurrentTime
sockList <- STM.newTMVarIO []
serverState <- STM.newTMVarIO (ServerState False False)
let initRead = ReaderContainer (arenaMap arena) setFPS sock let initRead = ReaderContainer (arenaMap arena) setFPS sock
initState = StateContainer (arenaSpawners arena) [] (ServerState False False) now [] initState = StateContainer (arenaSpawners arena) [] serverState now sockList
(finalState, finalWrite) <- execRWST runGame initRead initState (finalState, finalWrite) <- execRWST
(do
terminateGameOnSigint
runGame
)
initRead
initState
print finalWrite print finalWrite
where where
opts = info (options <**> helper) opts = info (options <**> helper)

View file

@ -1,12 +1,20 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Server.Communication where module Server.Communication where
import Control.Concurrent
import qualified Control.Concurrent.STM as STM
import Control.Monad import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Loops
import Control.Monad.RWS.Strict import Control.Monad.RWS.Strict
import Data.Maybe (maybe)
import Network.Socket as Net import Network.Socket as Net
import System.IO import System.IO
@ -17,6 +25,7 @@ import System.Posix.Signals
import Server.Types import Server.Types
import Server.Util import Server.Util
import Data.Maybe (isNothing)
-- | Function which determines whether the given filePath is a supported socket path and -- | Function which determines whether the given filePath is a supported socket path and
-- subsequently creates a socket in said location. -- subsequently creates a socket in said location.
@ -33,14 +42,19 @@ bindSocket path = do
Net.listen sock 5 Net.listen sock 5
pure sock pure sock
-- | Function that installs a handler on SIGINT to close and remove the given socket -- | Function that installs a handler on SIGINT to terminate game
terminateSocketOnSigint terminateGameOnSigint
:: Socket -- ^ Socket to terminate on termination :: Game ()
-> IO () terminateGameOnSigint = do
terminateSocketOnSigint sock = sock <- asks rcMainSocket
void $ installHandler clients <- liftIO . STM.atomically . STM.readTMVar =<< gets scClientSockets
serverState <- gets scServerState
void $ liftIO $ installHandler
keyboardSignal keyboardSignal
(CatchOnce $ do (CatchOnce $ do
void $ STM.atomically $ STM.swapTMVar serverState (ServerState False True)
disconnectClients clients
threadDelay (10 ^ 6)
(SockAddrUnix path) <- getSocketName sock (SockAddrUnix path) <- getSocketName sock
close' sock close' sock
removeIfExists path removeIfExists path
@ -48,29 +62,52 @@ terminateSocketOnSigint sock =
raiseSignal keyboardSignal raiseSignal keyboardSignal
) )
Nothing Nothing
where
disconnectClients = mapM_
(\(clientSocket, mThread) -> do
maybe (pure ()) killThread mThread
close' clientSocket
)
-- | Process incoming connection requests -- | Process incoming connection requests
processRequests :: Game processRequests :: Game ()
processRequests = do processRequests = do
mainSocket <- asks rcMainSocket mainSocket <- asks rcMainSocket
clientSock <- liftIO $ do socketList <- gets scClientSockets
(clientSock, _) <- accept mainSocket serverState <- gets scServerState
putStrLn $ "accepted new connection" void $ liftIO $ forkIO $ acceptConnection mainSocket socketList serverState
pure clientSock where
modify' (\st -> acceptConnection mainSocket socketList serverState = whileM_
st (not . serverStop <$> liftIO (STM.atomically $ STM.readTMVar serverState))
{scClientSockets = clientSock : scClientSockets st} (do
) (clientSock, _) <- accept mainSocket
putStrLn "accepted new connection"
liftIO $ STM.atomically $ do
list <- STM.takeTMVar socketList
STM.putTMVar socketList ((clientSock, Nothing) : list)
)
-- | process incomeing messages from clients -- | process incoming messages from clients
processMessages :: Game processMessages :: Game ()
processMessages = do processMessages = do
clientSocks <- gets scClientSockets clientsVar <- gets scClientSockets
mapM_ clients <- liftIO $ STM.atomically $ STM.readTMVar $ clientsVar
(\clientSocket -> liftIO $ do newClients <- mapM
connectionHandle <- socketToHandle clientSocket ReadMode (\client@(clientSocket, mThread) ->
hSetBuffering connectionHandle LineBuffering if isNothing mThread
messages <- hGetContents' connectionHandle then liftIO $ do
print messages connectionHandle <- socketToHandle clientSocket ReadMode
thread <- forkIO
(listenTo connectionHandle)
pure (clientSocket, Just thread)
else
pure client
) )
clientSocks clients
liftIO $ STM.atomically $ do
void $ STM.swapTMVar clientsVar newClients
where
listenTo connectionHandle = do
hSetBuffering connectionHandle LineBuffering
message <- hGetContents' connectionHandle
putStr message

View file

@ -1,13 +1,22 @@
{-# LANGUAGE OverloadedStrings #-}
module Server.Game where module Server.Game where
import Control.Concurrent (threadDelay) import Control.Concurrent (threadDelay, killThread)
import qualified Control.Concurrent.STM as STM
import Control.Monad.RWS.Strict import Control.Monad.RWS.Strict
import Control.Monad.Loops import Control.Monad.Loops
import qualified Data.ByteString.Char8 as B8
import Data.Time import Data.Time
import Data.String (fromString)
import System.IO (stdout)
-- internal imports -- internal imports
import Library.Types import Library.Types
@ -15,26 +24,31 @@ import Library.Types
import Server.Communication import Server.Communication
import Server.Types import Server.Types
runGame :: Game runGame :: Game ()
runGame = do runGame = do
processRequests
whileM_ whileM_
(not . serverStop <$> gets scServerState) (not . serverStop <$> (liftIO . STM.atomically . STM.readTMVar =<< gets scServerState))
(do (do
before <- gets scServerLastTick before <- gets scServerLastTick
now <- liftIO getCurrentTime now <- liftIO getCurrentTime
let delta = realToFrac $ diffUTCTime now before let delta = realToFrac $ diffUTCTime now before
liftIO $ B8.hPutStr stdout $ "tick: " <> fromString (show delta) <> " \r"
processRequests
processMessages processMessages
updateSpawners delta updateSpawners delta
updateWizards delta updateWizards delta
modify'
(\s -> s
{ scServerLastTick = now
}
)
fps <- asks rcFPS fps <- asks rcFPS
let remainingTime = recip (fromIntegral fps) - delta let remainingTime = recip (fromIntegral fps) - delta
when (remainingTime > 0) $ when (remainingTime > 0) $
liftIO $ threadDelay $ floor $ remainingTime * 10 ^ 6 liftIO $ threadDelay $ floor $ remainingTime * 10 ^ 6
) )
updateSpawners :: Float -> Game updateSpawners :: Float -> Game ()
updateSpawners dt = updateSpawners dt =
modify' (\sc@(StateContainer spawners _ _ _ _) -> modify' (\sc@(StateContainer spawners _ _ _ _) ->
let newSpawners = map let newSpawners = map
@ -55,7 +69,7 @@ updateSpawners dt =
} }
) )
updateWizards :: Float -> Game updateWizards :: Float -> Game ()
updateWizards dt = updateWizards dt =
modify' (\sc@(StateContainer _ wizards _ _ _) -> modify' (\sc@(StateContainer _ wizards _ _ _) ->
let newWizards = map let newWizards = map

View file

@ -1,6 +1,10 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Server.Types where module Server.Types where
import Control.Concurrent (ThreadId)
import qualified Control.Concurrent.STM as STM
import Control.Monad.RWS.Strict import Control.Monad.RWS.Strict
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
@ -13,6 +17,8 @@ import Network.Socket
import Options.Applicative as O import Options.Applicative as O
--internal imports
import Library.Types import Library.Types
data Settings = Settings data Settings = Settings
@ -49,9 +55,9 @@ data ReaderContainer = ReaderContainer
data StateContainer = StateContainer data StateContainer = StateContainer
{ scSpawners :: [ Spawner ] { scSpawners :: [ Spawner ]
, scPlayers :: [ Wizard ] , scPlayers :: [ Wizard ]
, scServerState :: ServerState , scServerState :: STM.TMVar ServerState
, scServerLastTick :: UTCTime , scServerLastTick :: UTCTime
, scClientSockets :: [ Socket ] , scClientSockets :: STM.TMVar [ (Socket, Maybe ThreadId) ]
} }
-- | Data object for storing the server's state -- | Data object for storing the server's state
@ -61,4 +67,4 @@ data ServerState = ServerState
} }
deriving (Show, Eq) deriving (Show, Eq)
type Game = RWST ReaderContainer String StateContainer IO () type Game = RWST ReaderContainer String StateContainer IO

View file

@ -63,6 +63,7 @@ executable wizard-wipeout-server
, text , text
, time , time
, random , random
, stm
, unix , unix
, wizard-wipeout , wizard-wipeout
, yaml , yaml