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

196 lines
5.9 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
import Data.UUID
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
import System.Random (randomRIO)
2024-05-01 21:52:49 +00:00
-- internal imports
import Library.Types
import Server.Types
-- | Sends a specified message through given socket to the client
2024-10-31 18:19:13 +00:00
queueMessage
2024-05-01 21:52:49 +00:00
:: ServerMessage
-> UUID
2024-11-03 03:40:46 +00:00
-> [ClientQueue]
2024-05-01 21:52:49 +00:00
-> IO ()
2024-11-03 03:40:46 +00:00
queueMessage msg uuid queueList = do
putStrLn $ "queueing message \"" <> show msg <> "\" for client " <> show uuid <> ""
let mQueue = cqQueue <$> find (\client -> cqUUID client == Just uuid) queueList
2024-05-01 21:52:49 +00:00
maybe
2024-11-03 03:40:46 +00:00
(putStrLn $ "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-03 03:40:46 +00:00
putStrLn "message queued!"
2024-10-31 18:19:13 +00:00
sendMessageQueue
:: STM.TMVar Socket
-> STM.TQueue ServerMessage
-> IO ()
sendMessageQueue sockContainer queue = do
2024-11-03 03:40:46 +00:00
msgs <- STM.atomically $ STM.flushTQueue queue
mapM_
(\msg -> do
sock <- STM.atomically $ STM.readTMVar sockContainer
putStrLn "read socket container for sending"
putStrLn $ "sending message: " <> show msg
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) ->
putStrLn $ "can't reach client after " <> show e
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
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
queues <- STM.atomically $ STM.readTMVar (scClientQueues stateContainer)
queueMessage
( 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)
putStrLn "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-03 03:40:46 +00:00
:: STM.TMVar [ClientSocket]
2024-05-01 21:52:49 +00:00
-> Socket
-> IO ()
dropClient clientList sock = do
mClient <- STM.atomically $ do
clients <- STM.readTMVar clientList
2024-11-03 03:40:46 +00:00
let mclient = find (\client -> csSocket client == sock) clients
let reducedClients = filter (\client -> csSocket client /= sock) clients
2024-05-01 21:52:49 +00:00
void $ STM.swapTMVar clientList reducedClients
pure mclient
maybe
(putStrLn $ "closing unknown socket: " <> show sock)
2024-05-01 21:52:49 +00:00
(\client -> do
2024-11-03 03:40:46 +00:00
putStrLn $ "dropping client because of closed socket: " <> show (fromJust $ csUUID client)
killThread (csSender client)
killThread (csReceiver client)
2024-05-01 21:52:49 +00:00
)
mClient
close sock
2024-06-09 05:32:03 +00:00
sendUpdate
:: StateContainer
-> ServerMap
-> Player
-> IO ()
sendUpdate 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
correctionLeft = if wizardRot < pi / 2 || wizardRot > 2 * pi
then ceiling
else floor
correctionRight = if wizardRot < pi / 2 || wizardRot > 2 * pi
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
queues <- STM.atomically $ STM.readTMVar $ scClientQueues stateContainer
queueMessage msg playerId queues