gameServer/NetRoutines.hs
author smxx
Thu, 04 Feb 2010 14:48:49 +0000
changeset 2745 11fce231f24a
parent 2403 6c5d504af2ba
child 2867 9be6693c78cb
permissions -rw-r--r--
Engine: + Split PlaySound into PlaySound and LoopSound + Added overloaded versions of PlaySound/LoopSound that won't require voicepack parameter + LoopSound now allows multiple copies of the same sound to play looped and returns the channel used for playback (to stop them later) + StopSound now allows either a specific sound (single playback) or channel (single playback as well as looped playback) to be stopped + SoundChannel attribute for Gears to be used when looping sounds

{-# LANGUAGE ScopedTypeVariables #-}
module NetRoutines where

import Network
import Network.Socket
import System.IO
import Control.Concurrent
import Control.Concurrent.Chan
import Control.Concurrent.STM
import qualified Control.Exception as Exception
import Data.Time
-----------------------------
import CoreTypes
import ClientIO
import Utils

acceptLoop :: Socket -> Chan CoreMessage -> Int -> IO ()
acceptLoop servSock coreChan clientCounter = do
	Exception.handle
		(\(_ :: Exception.IOException) -> putStrLn "exception on connect") $
		do
		(socket, sockAddr) <- Network.Socket.accept servSock

		cHandle <- socketToHandle socket ReadWriteMode
		hSetBuffering cHandle LineBuffering
		clientHost <- sockAddr2String sockAddr

		currentTime <- getCurrentTime
		
		sendChan <- newChan

		let newClient =
				(ClientInfo
					nextID
					sendChan
					cHandle
					clientHost
					currentTime
					""
					""
					False
					0
					0
					0
					False
					False
					False
					undefined
					undefined
					)

		writeChan coreChan $ Accept newClient

		forkIO $ clientRecvLoop cHandle coreChan nextID
		forkIO $ clientSendLoop cHandle coreChan sendChan nextID
		return ()

	acceptLoop servSock coreChan nextID
	where
		nextID = clientCounter + 1