wizard-wipeout/src-server/Server/Communication/Send.hs

211 lines
6.8 KiB
Haskell
Raw Normal View History

2024-06-09 05:32:03 +00:00
{-# LANGUAGE RecordWildCards #-}
2024-05-01 21:52:49 +00:00
module Server.Communication.Send where
import Control.Concurrent
import qualified Control.Concurrent.STM as STM
import Control.Exception
import Control.Monad
import Control.Monad.Reader
import Control.Monad.State
import qualified Data.Aeson as A
2024-06-09 05:32:03 +00:00
import qualified Data.Matrix as M
2024-05-01 21:52:49 +00:00
import Data.Maybe
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy.Char8 as B8
import Data.Time
import qualified Data.Vector.Storable as VS
import Data.List
2024-11-03 10:51:13 +00:00
import Data.UUID hiding (null)
2024-05-01 21:52:49 +00:00
import Data.UUID.V4
2024-06-09 05:32:03 +00:00
import Linear
2024-05-01 21:52:49 +00:00
import Network.Socket
-- internal imports
import Library.Types
2024-11-04 09:58:51 +00:00
import Server.Log (logPrintIO)
2024-05-01 21:52:49 +00:00
import Server.Types
-- | Sends a specified message through given socket to the client
2024-10-31 18:19:13 +00:00
queueMessage
2024-11-04 05:53:58 +00:00
:: LogLevel
-> ServerMessage
2024-05-01 21:52:49 +00:00
-> UUID
2024-11-03 10:51:13 +00:00
-> STM.TMVar [ClientQueue]
2024-05-01 21:52:49 +00:00
-> IO ()
2024-11-04 05:53:58 +00:00
queueMessage curLevel msg uuid queueListContainer = do
2024-11-03 10:51:13 +00:00
queueList <- STM.atomically $ STM.readTMVar queueListContainer
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Verbose $ "queueing message \"" <> show msg <> "\" for client " <> show uuid <> ""
2024-11-03 03:40:46 +00:00
let mQueue = cqQueue <$> find (\client -> cqUUID client == Just uuid) queueList
2024-05-01 21:52:49 +00:00
maybe
2024-11-04 05:53:58 +00:00
(logPrintIO curLevel Warning $ "no queue found for client: " <> show uuid)
2024-10-31 18:19:13 +00:00
(\queue ->
STM.atomically $ STM.writeTQueue queue msg
)
mQueue
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Verbose "message queued!"
2024-10-31 18:19:13 +00:00
sendMessageQueue
2024-11-04 05:53:58 +00:00
:: LogLevel
-> STM.TMVar Socket
2024-10-31 18:19:13 +00:00
-> STM.TQueue ServerMessage
-> IO ()
2024-11-04 05:53:58 +00:00
sendMessageQueue curLevel sockContainer queue = do
2024-11-03 10:51:13 +00:00
-- randTime <- randomRIO (1, 1000)
-- threadDelay randTime
2024-11-03 03:40:46 +00:00
msgs <- STM.atomically $ STM.flushTQueue queue
2024-11-04 05:53:58 +00:00
unless (null msgs) $ logPrintIO curLevel Verbose $ "messages in queue: " <> show msgs
2024-11-03 03:40:46 +00:00
mapM_
(\msg -> do
sock <- STM.atomically $ STM.readTMVar sockContainer
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Verbose "read socket container for sending"
logPrintIO curLevel Verbose $ "sending message: " <> show msg
2024-11-03 03:40:46 +00:00
let msgJson = A.encode msg
msgVector = VS.fromList $ B.unpack $ B.toStrict ('<' `B8.cons` (msgJson `B8.snoc` '>'))
VS.unsafeWith
msgVector
(\ptr -> do
eResult <- try $ void $ sendBuf sock ptr (VS.length msgVector)
case eResult of
Left (e :: IOException) ->
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Error $ "can't reach client after " <> show e
2024-11-03 03:40:46 +00:00
Right _ ->
pure ()
2024-05-01 21:52:49 +00:00
)
2024-10-31 18:19:13 +00:00
)
2024-11-03 03:40:46 +00:00
msgs
2024-05-01 21:52:49 +00:00
sendPings :: Game ()
sendPings = do
now <- liftIO getCurrentTime
maxTimeout <- asks rcClientMaxTimeout
framesPerPing <- asks rcFramesPerPing
2024-11-04 05:53:58 +00:00
curLevel <- asks rcLogLevel
2024-05-01 21:52:49 +00:00
fps <- asks rcFPS
stateContainer <- get
players <- liftIO $ STM.atomically $ STM.readTMVar (scPlayers stateContainer)
2024-11-03 03:40:46 +00:00
-- sockets <- liftIO $ STM.atomically $ STM.readTMVar (scClientSockets stateContainer)
2024-05-01 21:52:49 +00:00
mapM_
(\player@(Player plId (Wizard {}) readiness (lastPongTime, _)) -> do
let timeDiff = realToFrac $ diffUTCTime now lastPongTime :: Float
when (readiness && timeDiff > (fromIntegral framesPerPing * recip (fromIntegral fps))) $ do
2024-11-03 03:40:46 +00:00
-- let clientSock = ccSocket <$> find (\c -> ccUUID c == Just plId) sockets
-- when (isJust clientSock) $
-- if timeDiff > realToFrac maxTimeout
-- then do
-- liftIO $ do
-- putStrLn $ "dropping client because of timeout: " <> show plId
-- dropClient (scClientSockets stateContainer) (fromJust clientSock)
-- put stateContainer
-- else do
2024-05-01 21:52:49 +00:00
random <- liftIO nextRandom
2024-10-31 20:01:53 +00:00
let newPong = (now, random)
2024-11-03 03:40:46 +00:00
liftIO $ do
2024-11-03 10:51:13 +00:00
let queues = scClientQueues stateContainer
2024-11-03 03:40:46 +00:00
queueMessage
2024-11-04 05:53:58 +00:00
curLevel
2024-11-03 03:40:46 +00:00
( Ping random
)
plId
queues
2024-05-01 21:52:49 +00:00
let newPlayer = player
{ playerLastPong = newPong
}
otherPlayers = filter (\a -> playerId a /= plId) players
2024-11-03 03:40:46 +00:00
liftIO $ do
void $ STM.atomically $
STM.swapTMVar (scPlayers stateContainer) (newPlayer : otherPlayers)
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Verbose "ping!"
2024-05-01 21:52:49 +00:00
)
players
put stateContainer
-- | Drops the client from internal management and closes its socket, if still present.
dropClient
2024-11-04 05:53:58 +00:00
:: LogLevel
-> STM.TMVar [ClientSocket]
2024-11-03 14:22:28 +00:00
-> STM.TMVar [ClientQueue]
2024-05-01 21:52:49 +00:00
-> Socket
-> IO ()
2024-11-04 05:53:58 +00:00
dropClient curLevel socketList queueList sock = do
2024-11-03 14:22:28 +00:00
clients <- STM.atomically $ STM.readTMVar socketList
2024-05-01 21:52:49 +00:00
mClient <- STM.atomically $ do
2024-11-03 03:40:46 +00:00
let mclient = find (\client -> csSocket client == sock) clients
2024-05-01 21:52:49 +00:00
pure mclient
maybe
2024-11-04 05:53:58 +00:00
(logPrintIO curLevel Warning $ "closing unknown socket: " <> show sock)
2024-05-01 21:52:49 +00:00
(\client -> do
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Info $ "killing client sender and listener because of socket closing: " <> show (fromJust $ csUUID client)
2024-11-03 03:40:46 +00:00
killThread (csSender client)
killThread (csReceiver client)
2024-11-04 05:53:58 +00:00
logPrintIO curLevel Info $ "dropping client because of socket closing: " <> show (fromJust $ csUUID client)
2024-05-01 21:52:49 +00:00
)
mClient
2024-11-03 14:22:28 +00:00
STM.atomically $ do
queues <- STM.readTMVar queueList
let reducedClients = filter (\client -> csSocket client /= sock) clients
reducedQueues = filter (\queue -> cqUUID queue /= csUUID (fromJust mClient)) queues
void $ STM.swapTMVar socketList reducedClients
void $ STM.swapTMVar queueList reducedQueues
2024-05-01 21:52:49 +00:00
close sock
2024-06-09 05:32:03 +00:00
sendUpdate
2024-11-04 05:53:58 +00:00
:: LogLevel
-> StateContainer
2024-06-09 05:32:03 +00:00
-> ServerMap
-> Player
-> IO ()
2024-11-04 05:53:58 +00:00
sendUpdate curLevel stateContainer tileMap player = do
2024-11-03 03:40:46 +00:00
let slice = buildSlice player
2024-06-09 05:32:03 +00:00
sendSlice slice player
where
2024-11-03 03:40:46 +00:00
buildSlice :: Player -> MapSlice
buildSlice (Player _ (Wizard {..}) _ _) =
2024-06-09 05:32:03 +00:00
let V2 wr wc = wizardPos
subCoords = (,) <$> [floor wr - 4 .. floor wr + 4] <*> [floor wc - 4 .. floor wc + 4]
leftBound = wizardRot + (pi / 4)
rightBound = wizardRot - (pi / 4)
leftLine row = cos leftBound * row
rightLine row = sin rightBound * row
2024-11-25 02:48:18 +00:00
correctionLeft = if wizardRot < pi / 2 || wizardRot >= 2 * pi
then floor
else ceiling
correctionRight = if wizardRot < pi / 2 || wizardRot >= 2 * pi
2024-06-09 05:32:03 +00:00
then ceiling
else floor
initViewMatrix = M.fromList 9 9 $ map
(\(qr, qc) ->
if qc - floor wc <= correctionLeft (leftLine (wr - fromIntegral qr))
&& qc - floor wc >= correctionRight (rightLine (wr - fromIntegral qr))
then
M.safeGet qr qc tileMap
else
Nothing
)
subCoords
2024-11-03 03:40:46 +00:00
in
MapSlice initViewMatrix []
2024-06-09 05:32:03 +00:00
sendSlice :: MapSlice -> Player -> IO ()
sendSlice slice (Player playerId wizard _ _) = do
let msg = TickUpdate slice wizard
-- print slice
2024-11-03 03:40:46 +00:00
liftIO $ do
2024-11-03 10:51:13 +00:00
let queues = scClientQueues stateContainer
2024-11-04 05:53:58 +00:00
queueMessage curLevel msg playerId queues