author | unc0rr |
Thu, 09 Oct 2008 21:00:42 +0000 | |
changeset 1340 | 430d210d54ae |
parent 1321 | d7dc4e86201e |
child 1341 | 86d7d5ab22a2 |
permissions | -rw-r--r-- |
877 | 1 |
module Main where |
2 |
||
3 |
import Network |
|
4 |
import IO |
|
5 |
import System.IO |
|
6 |
import Control.Concurrent |
|
7 |
import Control.Concurrent.STM |
|
1307 | 8 |
import Control.Exception (setUncaughtExceptionHandler, handle, finally) |
890 | 9 |
import Control.Monad (forM, forM_, filterM, liftM) |
1308
d5dcd6cfa5e2
Fix another server failure (when second client in room disconnects)
unc0rr
parents:
1307
diff
changeset
|
10 |
import Maybe (fromMaybe) |
890 | 11 |
import Data.List |
877 | 12 |
import Miscutils |
890 | 13 |
import HWProto |
877 | 14 |
|
889 | 15 |
acceptLoop :: Socket -> TChan ClientInfo -> IO () |
877 | 16 |
acceptLoop servSock acceptChan = do |
17 |
(cHandle, host, port) <- accept servSock |
|
18 |
cChan <- atomically newTChan |
|
19 |
forkIO $ clientLoop cHandle cChan |
|
894 | 20 |
atomically $ writeTChan acceptChan (ClientInfo cChan cHandle "" 0 "" False) |
1082 | 21 |
hPutStrLn cHandle "CONNECTED\n" |
1340
430d210d54ae
Flush CONNECTED message, so client hasn't to wait for it on connect
unc0rr
parents:
1321
diff
changeset
|
22 |
hFlush cHandle |
877 | 23 |
acceptLoop servSock acceptChan |
24 |
||
1307 | 25 |
|
1082 | 26 |
listenLoop :: Handle -> [String] -> TChan [String] -> IO () |
27 |
listenLoop handle buf chan = do |
|
877 | 28 |
str <- hGetLine handle |
1082 | 29 |
if str == "" then do |
30 |
atomically $ writeTChan chan buf |
|
31 |
listenLoop handle [] chan |
|
32 |
else |
|
33 |
listenLoop handle (buf ++ [str]) chan |
|
877 | 34 |
|
1307 | 35 |
|
1082 | 36 |
clientLoop :: Handle -> TChan [String] -> IO () |
877 | 37 |
clientLoop handle chan = |
1082 | 38 |
listenLoop handle [] chan |
877 | 39 |
`catch` (const $ clientOff >> return ()) |
1309 | 40 |
where clientOff = atomically $ writeTChan chan ["QUIT"] -- if the client disconnects, we perform as if it sent QUIT message |
877 | 41 |
|
1307 | 42 |
|
1306 | 43 |
sendAnswers [] _ clients _ = return clients |
44 |
sendAnswers ((handlesFunc, answer):answers) client clients rooms = do |
|
45 |
let recipients = handlesFunc client clients rooms |
|
1321 | 46 |
putStrLn ("< " ++ (show answer)) |
1306 | 47 |
|
48 |
clHandles' <- forM recipients $ |
|
1307 | 49 |
\ch -> Control.Exception.handle (\e -> putStrLn (show e) >> hClose ch >> return [ch]) $ |
1309 | 50 |
if (not $ null answer) && (head answer == "off") then hClose ch >> return [ch] else -- probably client with exception, don't send him anything |
1307 | 51 |
do |
1306 | 52 |
forM_ answer (\str -> hPutStrLn ch str) |
53 |
hPutStrLn ch "" |
|
54 |
hFlush ch |
|
55 |
if (not $ null answer) && (head answer == "BYE") then hClose ch >> return [ch] else return [] |
|
56 |
||
57 |
let mclients = remove clients $ concat clHandles' |
|
58 |
||
59 |
sendAnswers answers client mclients rooms |
|
60 |
where |
|
1307 | 61 |
remove list rmClHandles = deleteFirstsBy2t (\ a b -> (Miscutils.handle a) == b) list rmClHandles |
1306 | 62 |
|
63 |
||
889 | 64 |
mainLoop :: Socket -> TChan ClientInfo -> [ClientInfo] -> [RoomInfo] -> IO () |
65 |
mainLoop servSock acceptChan clients rooms = do |
|
877 | 66 |
r <- atomically $ (Left `fmap` readTChan acceptChan) `orElse` (Right `fmap` tselect clients) |
67 |
case r of |
|
889 | 68 |
Left ci -> do |
69 |
mainLoop servSock acceptChan (ci:clients) rooms |
|
1082 | 70 |
Right (cmd, client) -> do |
1302 | 71 |
putStrLn ("> " ++ show cmd) |
1307 | 72 |
|
1305 | 73 |
let (clientsFunc, roomsFunc, answers) = handleCmd client clients rooms $ cmd |
1082 | 74 |
let mrooms = roomsFunc rooms |
1308
d5dcd6cfa5e2
Fix another server failure (when second client in room disconnects)
unc0rr
parents:
1307
diff
changeset
|
75 |
let mclients = (clientsFunc clients) |
d5dcd6cfa5e2
Fix another server failure (when second client in room disconnects)
unc0rr
parents:
1307
diff
changeset
|
76 |
let mclient = fromMaybe client $ find (== client) mclients |
1305 | 77 |
|
1308
d5dcd6cfa5e2
Fix another server failure (when second client in room disconnects)
unc0rr
parents:
1307
diff
changeset
|
78 |
clientsIn <- sendAnswers answers mclient mclients mrooms |
1306 | 79 |
|
1307 | 80 |
mainLoop servSock acceptChan clientsIn mrooms |
81 |
||
877 | 82 |
|
83 |
startServer serverSocket = do |
|
84 |
acceptChan <- atomically newTChan |
|
85 |
forkIO $ acceptLoop serverSocket acceptChan |
|
889 | 86 |
mainLoop serverSocket acceptChan [] [] |
877 | 87 |
|
1307 | 88 |
|
878 | 89 |
main = withSocketsDo $ do |
877 | 90 |
serverSocket <- listenOn $ Service "hedgewars" |
91 |
startServer serverSocket `finally` sClose serverSocket |