wizard-wipeout/src-client/Main.hs
2024-11-03 11:19:19 +01:00

128 lines
3.4 KiB
Haskell

module Main where
import Control.Concurrent (threadDelay)
import qualified Control.Concurrent.STM as STM
import Control.Monad
import Control.Monad.RWS
import Data.IORef
import qualified Data.Matrix as M
import Graphics.Vty
import Graphics.Vty.CrossPlatform
import Network.Socket (Socket, close)
import Options.Applicative
-- internal imports
import Client.Communication
import Client.Game
import Client.Types
import Library.Types
main :: IO ()
main = do
putStrLn "Hello, Arena!"
(Options socketLocation) <- execParser opts
putStrLn $ "connecting to Socket " <> socketLocation
sock <- connectSocket socketLocation
putStrLn "connected"
messageQueue <- STM.newTQueueIO
eventQueue <- STM.newTQueueIO
-- threadDelay $ 1 * 10 ^ 6
mockClientState <- STM.newTMVarIO (ClientState undefined False)
let mockState = StateContainer undefined mockClientState undefined undefined
sendMessage IdRequest sock
awaitResponse sock messageQueue mockState 0
clientIdMsg <- head <$> STM.atomically (STM.flushTQueue messageQueue)
let clientId = acClientUUID clientIdMsg
putStrLn $ "received client UUID: " <> show clientId
putStrLn welcomeText
threadDelay $ 5 * 10 ^ 6
sendMessage (ClientMessage clientId ClientRequestWizard) sock
-- threadDelay $ 1 * 10 ^ 6
awaitResponse sock messageQueue mockState 1
playerWizard <- head <$> STM.atomically (STM.flushTQueue messageQueue)
putStrLn $ "received wizard: " <> show (initWizard playerWizard)
vty <- mkVty defaultConfig
hideCursor (outputIface vty)
-- shut down graphical interface for now
-- shutdown vty
stopper <- newIORef False
clientState <- STM.newTMVarIO (ClientState vty False)
let initSlice = MapSlice (M.matrix 9 9 (const Nothing)) []
let initRead = ReaderContainer sock clientId messageQueue eventQueue
initState = StateContainer (initWizard playerWizard) clientState initSlice stopper
-- putStrLn "sending quit message"
-- sendMessage (ClientMessage clientId ClientQuit) sock
putStrLn "entering Game Monad"
void $ execRWST
(do
terminateGameOnSigint stopper
liftIO $ putStrLn "entering main game function"
runGame
)
initRead
initState
putStrLn "Shutting down client…"
showCursor (outputIface vty)
shutdown vty
threadDelay (10 ^ 3)
putStrLn "Closing connection to server…"
close sock
putStrLn "bye bye"
where
opts = info (options <**> helper)
( fullDesc
<> progDesc "Run the \"wizard-wipeout\" Client."
<> header "wizard-wipeout - Last Mage standing"
)
welcomeText :: String
welcomeText = mconcat $ map (<> "\n")
[ "Welcome to the arena, wizards."
, ""
, "Let the toughest and bravest of you survive"
, ""
, "Some last hints before you enter the fighting grounds:"
, ""
, "press [SPACE] to fire your wand"
, "press [1] through [9] to change wands, if you have collected more wands"
, "press [ESC] to leave"
, ""
, "Good Luck!"
]
awaitResponse
:: Socket
-> STM.TQueue ServerMessage
-> StateContainer
-> Int
-> IO ()
awaitResponsea _ _ _ 10 = error "Tries to communicate with server exceeded"
awaitResponse sock messageQueue mockState numTries = do
receiveMessage sock messageQueue mockState
responsePresent <- not <$> STM.atomically (STM.isEmptyTQueue messageQueue)
if responsePresent
then pure ()
else do
threadDelay $ 10 ^ 6
awaitResponse sock messageQueue mockState (succ numTries)