netserver/newhwserv.hs
author unc0rr
Tue, 15 Jul 2008 16:40:50 +0000
changeset 1081 5be338fa4e2c
parent 901 2f5ce9a584f9
child 1082 596b1dcdc1df
permissions -rw-r--r--
First steps to switch hedgewars to new net protocol
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     1
module Main where
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     2
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     3
import Network
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     4
import IO
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     5
import System.IO
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     6
import Control.Concurrent
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     7
import Control.Concurrent.STM
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
     8
import Control.Exception (finally)
890
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
     9
import Control.Monad (forM, forM_, filterM, liftM)
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
    10
import Data.List
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    11
import Miscutils
890
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
    12
import HWProto
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    13
889
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    14
acceptLoop :: Socket -> TChan ClientInfo -> IO ()
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    15
acceptLoop servSock acceptChan = do
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    16
	(cHandle, host, port) <- accept servSock
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    17
	cChan <- atomically newTChan
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    18
	forkIO $ clientLoop cHandle cChan
894
2ca76a7f3121 - Fixed some bugs
unc0rr
parents: 893
diff changeset
    19
	atomically $ writeTChan acceptChan (ClientInfo cChan cHandle "" 0 "" False)
1081
5be338fa4e2c First steps to switch hedgewars to new net protocol
unc0rr
parents: 901
diff changeset
    20
	hPutStrLn cHandle "CONNECTED"
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    21
	acceptLoop servSock acceptChan
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    22
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    23
listenLoop :: Handle -> TChan String -> IO ()
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    24
listenLoop handle chan = do
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    25
	str <- hGetLine handle
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    26
	atomically $ writeTChan chan str
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    27
	listenLoop handle chan
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    28
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    29
clientLoop :: Handle -> TChan String -> IO ()
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    30
clientLoop handle chan =
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    31
	listenLoop handle chan
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    32
		`catch` (const $ clientOff >> return ())
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    33
	where clientOff = atomically $ writeTChan chan "QUIT"
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    34
889
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    35
mainLoop :: Socket -> TChan ClientInfo -> [ClientInfo] -> [RoomInfo] -> IO ()
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    36
mainLoop servSock acceptChan clients rooms = do
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    37
	r <- atomically $ (Left `fmap` readTChan acceptChan) `orElse` (Right `fmap` tselect clients)
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    38
	case r of
889
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    39
		Left ci -> do
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    40
			mainLoop servSock acceptChan (ci:clients) rooms
901
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    41
		Right (line, clhandle) -> do
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    42
			let (mclients, mrooms, recipients, strs) = handleCmd clhandle clients rooms $ words line
890
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
    43
901
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    44
			clHandles' <- forM recipients $
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    45
					\ch -> do
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    46
							forM_ strs (\str -> hPutStrLn ch str)
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    47
							hFlush ch
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    48
							if (not $ null strs) && (head strs == "ROOMABANDONED") then hClose ch >> return [ch] else return []
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    49
					`catch` const (hClose ch >> return [ch])
890
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
    50
901
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    51
			clHandle' <- if (not $ null strs) && (head strs == "QUIT") then hClose clhandle >> return [clhandle] else return []
891
701f86df9b4c Properly handle QUIT command. Now, we can concentrate on protocol implementation
unc0rr
parents: 890
diff changeset
    52
901
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    53
			mainLoop servSock acceptChan (remove (remove mclients (concat clHandles')) clHandle') mrooms
890
1d8c4a5ec622 - Improve server core
unc0rr
parents: 889
diff changeset
    54
			where
901
2f5ce9a584f9 Modify protocol implementation functions interface (convertation not yet finished)
unc0rr
parents: 898
diff changeset
    55
				remove list rmClHandles = deleteFirstsBy2t (\ a b -> (handle a) == b) list rmClHandles
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    56
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    57
startServer serverSocket = do
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    58
	acceptChan <- atomically newTChan
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    59
	forkIO $ acceptLoop serverSocket acceptChan
889
3bf9dc791f45 Some work on newhwserv
unc0rr
parents: 878
diff changeset
    60
	mainLoop serverSocket acceptChan [] []
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    61
878
45bff6dadfce - Fix baseball bat
unc0rr
parents: 877
diff changeset
    62
main = withSocketsDo $ do
877
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    63
	serverSocket <- listenOn $ Service "hedgewars"
ebb801acd8b9 Try new approach for netserver
unc0rr
parents:
diff changeset
    64
	startServer serverSocket `finally` sClose serverSocket