introduce proper exception handling
This commit is contained in:
parent
95193f5fd1
commit
be888101a0
2 changed files with 60 additions and 25 deletions
|
@ -2,6 +2,8 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
|
import Control.Concurrent (threadDelay)
|
||||||
|
|
||||||
import qualified Control.Concurrent.STM as STM
|
import qualified Control.Concurrent.STM as STM
|
||||||
|
|
||||||
import Control.Monad.RWS.Strict
|
import Control.Monad.RWS.Strict
|
||||||
|
@ -69,6 +71,7 @@ main = do
|
||||||
initRead
|
initRead
|
||||||
initState
|
initState
|
||||||
-- removeIfExists setSocketPath
|
-- removeIfExists setSocketPath
|
||||||
|
threadDelay 1000
|
||||||
putStrLn "bye bye"
|
putStrLn "bye bye"
|
||||||
where
|
where
|
||||||
opts = info (options <**> helper)
|
opts = info (options <**> helper)
|
||||||
|
|
|
@ -6,6 +6,8 @@ import Control.Concurrent
|
||||||
|
|
||||||
import qualified Control.Concurrent.STM as STM
|
import qualified Control.Concurrent.STM as STM
|
||||||
|
|
||||||
|
import Control.Exception.Base
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
|
@ -73,32 +75,42 @@ terminateGameOnSigint path = do
|
||||||
close sock
|
close sock
|
||||||
removeIfExists path
|
removeIfExists path
|
||||||
void $ STM.atomically $ STM.swapTMVar serverState (ServerState False True)
|
void $ STM.atomically $ STM.swapTMVar serverState (ServerState False True)
|
||||||
-- Raise SIGINT again so it does not get blocked
|
|
||||||
-- raiseSignal sigINT
|
|
||||||
)
|
)
|
||||||
Nothing
|
Nothing
|
||||||
|
|
||||||
|
-- | Disconnect all connected clients gracefully by announcing the server quitting
|
||||||
disconnectClients
|
disconnectClients
|
||||||
:: STM.TMVar [(Maybe UUID, Socket)]
|
:: STM.TMVar [(Maybe UUID, Socket)]
|
||||||
-> [(Maybe UUID, Socket)]
|
-> [(Maybe UUID, Socket)]
|
||||||
-> IO ()
|
-> IO ()
|
||||||
disconnectClients clientList = mapM_
|
disconnectClients clientList = mapM_
|
||||||
(\client@(_, clientSocket) -> do
|
(\client@(muuid, _) -> do
|
||||||
sendMessage ServerQuit clientSocket
|
maybe
|
||||||
dropClient clientList client
|
(pure ())
|
||||||
|
(\uuid -> do
|
||||||
|
sendMessage ServerQuit uuid clientList
|
||||||
|
dropClient clientList uuid
|
||||||
|
)
|
||||||
|
muuid
|
||||||
)
|
)
|
||||||
|
|
||||||
|
-- | Drops the client from internal management and closes its socket, if still present.
|
||||||
dropClient
|
dropClient
|
||||||
:: STM.TMVar [(Maybe UUID, Socket)]
|
:: STM.TMVar [(Maybe UUID, Socket)]
|
||||||
-> (Maybe UUID, Socket)
|
-> UUID
|
||||||
-> IO ()
|
-> IO ()
|
||||||
dropClient clientList (uuid, clientSocket) = do
|
dropClient clientList uuid = do
|
||||||
STM.atomically $ do
|
msock <- STM.atomically $ do
|
||||||
clients <- STM.readTMVar clientList
|
clients <- STM.readTMVar clientList
|
||||||
let reducedClients = filter ((/= uuid) . fst) clients
|
let msock = lookup (Just uuid) clients
|
||||||
|
let reducedClients = filter ((/= Just uuid) . fst) clients
|
||||||
void $ STM.swapTMVar clientList reducedClients
|
void $ STM.swapTMVar clientList reducedClients
|
||||||
|
pure msock
|
||||||
putStrLn $ "dropping client " <> show uuid
|
putStrLn $ "dropping client " <> show uuid
|
||||||
close clientSocket
|
maybe
|
||||||
|
(pure ())
|
||||||
|
close
|
||||||
|
msock
|
||||||
|
|
||||||
-- | Process incoming connection requests
|
-- | Process incoming connection requests
|
||||||
processRequests :: Game ()
|
processRequests :: Game ()
|
||||||
|
@ -119,15 +131,23 @@ processRequests = do
|
||||||
-- | Sends a specified message through given socket to the client
|
-- | Sends a specified message through given socket to the client
|
||||||
sendMessage
|
sendMessage
|
||||||
:: ServerMessage
|
:: ServerMessage
|
||||||
-> Socket
|
-> UUID
|
||||||
|
-> STM.TMVar [(Maybe UUID, Socket)]
|
||||||
-> IO ()
|
-> IO ()
|
||||||
sendMessage msg sock = do
|
sendMessage msg uuid clientList = do
|
||||||
let msgJson = A.encode msg
|
clients <- STM.atomically $ STM.readTMVar clientList
|
||||||
|
let msock = lookup (Just uuid) clients
|
||||||
|
msgJson = A.encode msg
|
||||||
msgVector = VS.fromList $ B.unpack $ B.toStrict $ ('<' `B8.cons` (msgJson `B8.snoc` '>'))
|
msgVector = VS.fromList $ B.unpack $ B.toStrict $ ('<' `B8.cons` (msgJson `B8.snoc` '>'))
|
||||||
-- putStrLn $ "sending: " <> B8.unpack msgJson
|
-- putStrLn $ "sending: " <> B8.unpack msgJson
|
||||||
|
maybe
|
||||||
|
(dropClient clientList uuid)
|
||||||
|
(\sock ->
|
||||||
VS.unsafeWith
|
VS.unsafeWith
|
||||||
msgVector
|
msgVector
|
||||||
(\ptr -> void $ sendBuf sock ptr (VS.length msgVector))
|
(\ptr -> void $ sendBuf sock ptr (VS.length msgVector))
|
||||||
|
)
|
||||||
|
msock
|
||||||
|
|
||||||
-- | receive incoming messages from clients
|
-- | receive incoming messages from clients
|
||||||
receiveMessages
|
receiveMessages
|
||||||
|
@ -137,8 +157,8 @@ receiveMessages
|
||||||
receiveMessages clientsVar queue = do
|
receiveMessages clientsVar queue = do
|
||||||
clients <- liftIO $ STM.atomically $ STM.readTMVar clientsVar
|
clients <- liftIO $ STM.atomically $ STM.readTMVar clientsVar
|
||||||
mapM_
|
mapM_
|
||||||
(\(_, clientSocket) -> do
|
(\(muuid, clientSocket) -> do
|
||||||
receiveMessage clientSocket queue
|
receiveMessage clientSocket queue muuid clientsVar
|
||||||
)
|
)
|
||||||
clients
|
clients
|
||||||
|
|
||||||
|
@ -160,12 +180,24 @@ handleMessages = do
|
||||||
receiveMessage
|
receiveMessage
|
||||||
:: Socket
|
:: Socket
|
||||||
-> STM.TQueue ClientMessage
|
-> STM.TQueue ClientMessage
|
||||||
|
-> Maybe UUID
|
||||||
|
-> STM.TMVar [(Maybe UUID, Socket)]
|
||||||
-> IO ()
|
-> IO ()
|
||||||
receiveMessage sock queue = do
|
receiveMessage sock queue muuid clientList = do
|
||||||
let maxBufferLength = 4096
|
let maxBufferLength = 4096
|
||||||
mmsg <- do
|
mmsg <- do
|
||||||
ptr <- mallocArray maxBufferLength
|
ptr <- mallocArray maxBufferLength
|
||||||
bufferLength <- recvBuf sock ptr maxBufferLength
|
ebufferLength <-
|
||||||
|
try $ recvBuf sock ptr maxBufferLength
|
||||||
|
bufferLength <- case ebufferLength of
|
||||||
|
Left (_ :: IOException) -> do
|
||||||
|
putStrLn "Socket vanished, cleaning up…"
|
||||||
|
maybe
|
||||||
|
(pure ())
|
||||||
|
(dropClient clientList)
|
||||||
|
muuid
|
||||||
|
pure 0
|
||||||
|
Right len -> pure len
|
||||||
msg <- B.pack <$> peekArray bufferLength ptr
|
msg <- B.pack <$> peekArray bufferLength ptr
|
||||||
let mJsonMsg = A.decode' $ B8.fromStrict msg :: Maybe ClientMessage
|
let mJsonMsg = A.decode' $ B8.fromStrict msg :: Maybe ClientMessage
|
||||||
free ptr
|
free ptr
|
||||||
|
@ -208,7 +240,7 @@ handleMessage stateContainer readerContainer msg = do
|
||||||
clients
|
clients
|
||||||
void $ liftIO $ STM.atomically $ STM.swapTMVar clientList newClients
|
void $ liftIO $ STM.atomically $ STM.swapTMVar clientList newClients
|
||||||
putStrLn $ "Accepted Client with UUID " <> show clientId
|
putStrLn $ "Accepted Client with UUID " <> show clientId
|
||||||
sendMessage (AcceptClient clientId) clientSock
|
sendMessage (AcceptClient clientId) clientId clientList
|
||||||
ClientMessage clientId payload ->
|
ClientMessage clientId payload ->
|
||||||
case payload of
|
case payload of
|
||||||
ClientQuit -> do
|
ClientQuit -> do
|
||||||
|
@ -230,8 +262,7 @@ handleMessage stateContainer readerContainer msg = do
|
||||||
currentPlayers <- STM.readTMVar (scPlayers stateContainer)
|
currentPlayers <- STM.readTMVar (scPlayers stateContainer)
|
||||||
void $ STM.swapTMVar (scPlayers stateContainer) $
|
void $ STM.swapTMVar (scPlayers stateContainer) $
|
||||||
Player clientId freshWizard False (now, uuid) : currentPlayers
|
Player clientId freshWizard False (now, uuid) : currentPlayers
|
||||||
let clientSock = fromJust $ lookup (Just clientId) clients
|
sendMessage (ProvideInitialWizard freshWizard) clientId clientList
|
||||||
sendMessage (ProvideInitialWizard freshWizard) clientSock
|
|
||||||
ClientReady -> do
|
ClientReady -> do
|
||||||
putStrLn $ "client " <> show clientId <> " is ready!"
|
putStrLn $ "client " <> show clientId <> " is ready!"
|
||||||
STM.atomically $ do
|
STM.atomically $ do
|
||||||
|
@ -278,7 +309,7 @@ sendPings = do
|
||||||
when (isJust clientSock) $
|
when (isJust clientSock) $
|
||||||
if timeDiff > realToFrac maxTimeout
|
if timeDiff > realToFrac maxTimeout
|
||||||
then do
|
then do
|
||||||
liftIO $ dropClient (scClientSockets stateContainer) (Just plId, fromJust clientSock)
|
liftIO $ dropClient (scClientSockets stateContainer) plId
|
||||||
put stateContainer
|
put stateContainer
|
||||||
else do
|
else do
|
||||||
random <- liftIO nextRandom
|
random <- liftIO nextRandom
|
||||||
|
@ -286,7 +317,8 @@ sendPings = do
|
||||||
liftIO $ sendMessage
|
liftIO $ sendMessage
|
||||||
( Ping random
|
( Ping random
|
||||||
)
|
)
|
||||||
(fromJust clientSock)
|
plId
|
||||||
|
(scClientSockets stateContainer)
|
||||||
let newPlayer = player
|
let newPlayer = player
|
||||||
{ playerLastPong = newPong
|
{ playerLastPong = newPong
|
||||||
}
|
}
|
||||||
|
|
Loading…
Reference in a new issue