gameServer/ServerCore.hs
author unc0rr
Tue, 24 Feb 2009 19:39:49 +0000
changeset 1839 5dd4cb7fd7e5
parent 1833 e901ec5644b4
child 1841 fba7210b438b
permissions -rw-r--r--
Server now send ASKPASSWORD command to frontend when user has web account

module ServerCore where

import Network
import Control.Concurrent
import Control.Concurrent.STM
import Control.Concurrent.Chan
import Control.Monad
import qualified Data.IntMap as IntMap
import System.Log.Logger
--------------------------------------
import CoreTypes
import NetRoutines
import Utils
import HWProtoCore
import Actions
import OfficialServer.DBInteraction


firstAway (_, a, b, c) = (a, b, c)

reactCmd :: ServerInfo -> Int -> [String] -> Clients -> Rooms -> IO (ServerInfo, Clients, Rooms)
reactCmd serverInfo clID cmd clients rooms = do
	(_ , serverInfo, clients, rooms) <-
		foldM processAction (clID, serverInfo, clients, rooms) $ handleCmd clID clients rooms cmd
	return (serverInfo, clients, rooms)

mainLoop :: ServerInfo -> Clients -> Rooms -> IO ()
mainLoop serverInfo clients rooms = do
	r <- readChan $ coreChan serverInfo
	
	(newServerInfo, mClients, mRooms) <-
		case r of
			Accept ci -> do
				let updatedClients = IntMap.insert (clientUID ci) ci clients
				infoM "Clients" ("New client: id " ++ (show $ clientUID ci))
				processAction
					(clientUID ci, serverInfo, updatedClients, rooms)
					(AnswerThisClient ["CONNECTED", "Hedgewars server http://www.hedgewars.org/"])
				return (serverInfo, updatedClients, rooms)

			ClientMessage (clID, cmd) -> do
				debugM "Clients" $ (show clID) ++ ": " ++ (show cmd)
				if clID `IntMap.member` clients then
					reactCmd serverInfo clID cmd clients rooms
					else
					do
					debugM "Clients" "Message from dead client"
					return (serverInfo, clients, rooms)

			ClientAccountInfo clID info ->
				if clID `IntMap.member` clients then
					liftM firstAway $ processAction
						(clID, serverInfo, clients, rooms)
						(ProcessAccountInfo info)
					else
					do
					debugM "Clients" "Got info for dead client"
					return (serverInfo, clients, rooms)
			

	{-			let hadRooms = (not $ null rooms) && (null mrooms)
					in unless ((not $ isDedicated serverInfo) && ((null clientsIn) || hadRooms)) $
						mainLoop serverInfo acceptChan messagesChan clientsIn mrooms -}

	mainLoop newServerInfo mClients mRooms

startServer :: ServerInfo -> Chan CoreMessage -> Socket -> IO ()
startServer serverInfo coreChan serverSocket = do
	putStrLn $ "Listening on port " ++ show (listenPort serverInfo)

	forkIO $
		acceptLoop
			serverSocket
			coreChan
			0

	return ()
	
{-	forkIO $ messagesLoop messagesChan
	forkIO $ timerLoop messagesChan-}

	startDBConnection $ serverInfo

	mainLoop serverInfo IntMap.empty (IntMap.singleton 0 newRoom)