fix socket file removal

This commit is contained in:
nek0 2023-12-12 11:21:25 +01:00
parent eda823bb17
commit 7339587bd1
4 changed files with 19 additions and 13 deletions

View file

@ -1,6 +1,8 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
module Client.Communication where module Client.Communication where
import Control.Concurrent (threadDelay)
import qualified Control.Concurrent.STM as STM import qualified Control.Concurrent.STM as STM
import Control.Monad (void) import Control.Monad (void)
@ -73,9 +75,9 @@ terminateGameOnSigint = do
void $ liftIO $ installHandler void $ liftIO $ installHandler
keyboardSignal keyboardSignal
(CatchOnce $ do (CatchOnce $ do
void $ STM.atomically $ STM.swapTMVar serverState (clientState { clientStop = True }) currentState <- STM.atomically $ STM.readTMVar clientState
threadDelay (10 ^ 6) threadDelay (10 ^ 6)
sendMessage sock (ClientMessage clientId ClientQuit) sendMessage (ClientMessage clientId ClientQuit) sock
close sock close sock
-- Raise SIGINT again so it does not get blocked -- Raise SIGINT again so it does not get blocked
raiseSignal keyboardSignal raiseSignal keyboardSignal

View file

@ -1,5 +1,7 @@
module Client.Types where module Client.Types where
import qualified Control.Concurrent.STM as STM
import Control.Monad.RWS import Control.Monad.RWS
import Data.UUID import Data.UUID
@ -28,9 +30,9 @@ data ReaderContainer = ReaderContainer
, rcClientUUID :: UUID , rcClientUUID :: UUID
} }
newtype StateContainer = StateContainer data StateContainer = StateContainer
{ scWizard :: Wizard { scWizard :: Wizard
, scClientState :: ClientState , scClientState :: STM.TMVar ClientState
} }
type Game = RWST ReaderContainer String StateContainer IO type Game = RWST ReaderContainer String StateContainer IO

View file

@ -26,6 +26,7 @@ import Server.Communication
import Server.Game import Server.Game
import Server.Map (generateArena) import Server.Map (generateArena)
import Server.Types import Server.Types
import Server.Util
main :: IO () main :: IO ()
main = do main = do
@ -56,12 +57,13 @@ main = do
initState = StateContainer (arenaSpawners arena) [] serverState now sockList messageQueue initState = StateContainer (arenaSpawners arena) [] serverState now sockList messageQueue
(finalState, finalWrite) <- execRWST (finalState, finalWrite) <- execRWST
(do (do
terminateGameOnSigint terminateGameOnSigint setSocketPath
runGame runGame
) )
initRead initRead
initState initState
print finalWrite removeIfExists setSocketPath
putStrLn "bye bye"
where where
opts = info (options <**> helper) opts = info (options <**> helper)
( fullDesc ( fullDesc

View file

@ -60,24 +60,24 @@ bindSocket path = do
-- | Function that installs a handler on SIGINT to terminate game -- | Function that installs a handler on SIGINT to terminate game
terminateGameOnSigint terminateGameOnSigint
:: Game () :: FilePath
terminateGameOnSigint = do -> Game ()
terminateGameOnSigint path = do
sock <- asks rcMainSocket sock <- asks rcMainSocket
clients <- liftIO . STM.atomically . STM.readTMVar =<< gets scClientSockets clients <- liftIO . STM.atomically . STM.readTMVar =<< gets scClientSockets
serverState <- gets scServerState serverState <- gets scServerState
void $ liftIO $ installHandler void $ liftIO $ installHandler
keyboardSignal sigINT
(CatchOnce $ do (CatchOnce $ do
putStrLn "SIGINT caught, terminating…"
void $ STM.atomically $ STM.swapTMVar serverState (ServerState False True) void $ STM.atomically $ STM.swapTMVar serverState (ServerState False True)
disconnectClients clients disconnectClients clients
threadDelay (10 ^ 6)
(SockAddrUnix path) <- getSocketName sock
close sock close sock
removeIfExists path removeIfExists path
-- Raise SIGINT again so it does not get blocked -- Raise SIGINT again so it does not get blocked
raiseSignal keyboardSignal raiseSignal sigINT
) )
Nothing (Just emptySignalSet)
where where
disconnectClients = mapM_ disconnectClients = mapM_
(\(_, clientSocket) -> do (\(_, clientSocket) -> do