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