1370
|
1 |
module Main where
|
|
2 |
|
|
3 |
import Network
|
|
4 |
import IO
|
|
5 |
import System.IO
|
|
6 |
import Control.Concurrent
|
|
7 |
import Control.Concurrent.STM
|
|
8 |
import Control.Exception (setUncaughtExceptionHandler, handle, finally)
|
1384
|
9 |
import Control.Monad (forM, forM_, filterM, liftM, when, unless)
|
1370
|
10 |
import Maybe (fromMaybe)
|
|
11 |
import Data.List
|
|
12 |
import Miscutils
|
|
13 |
import HWProto
|
|
14 |
import Opts
|
|
15 |
|
|
16 |
acceptLoop :: Socket -> TChan ClientInfo -> IO ()
|
|
17 |
acceptLoop servSock acceptChan = do
|
|
18 |
(cHandle, host, port) <- accept servSock
|
1384
|
19 |
hPutStrLn cHandle "CONNECTED\n"
|
|
20 |
hFlush cHandle
|
1370
|
21 |
cChan <- atomically newTChan
|
|
22 |
forkIO $ clientLoop cHandle cChan
|
|
23 |
atomically $ writeTChan acceptChan (ClientInfo cChan cHandle "" 0 "" False)
|
|
24 |
acceptLoop servSock acceptChan
|
|
25 |
|
|
26 |
|
|
27 |
listenLoop :: Handle -> [String] -> TChan [String] -> IO ()
|
|
28 |
listenLoop handle buf chan = do
|
|
29 |
str <- hGetLine handle
|
|
30 |
if str == "" then do
|
|
31 |
atomically $ writeTChan chan buf
|
|
32 |
listenLoop handle [] chan
|
|
33 |
else
|
|
34 |
listenLoop handle (buf ++ [str]) chan
|
|
35 |
|
|
36 |
|
|
37 |
clientLoop :: Handle -> TChan [String] -> IO ()
|
|
38 |
clientLoop handle chan =
|
|
39 |
listenLoop handle [] chan
|
|
40 |
`catch` (const $ clientOff >> return ())
|
|
41 |
where clientOff = atomically $ writeTChan chan ["QUIT"] -- if the client disconnects, we perform as if it sent QUIT message
|
|
42 |
|
|
43 |
|
|
44 |
sendAnswers [] _ clients _ = return clients
|
|
45 |
sendAnswers ((handlesFunc, answer):answers) client clients rooms = do
|
|
46 |
let recipients = handlesFunc client clients rooms
|
1381
|
47 |
unless (null recipients) $ putStrLn ("< " ++ (show answer))
|
1370
|
48 |
|
|
49 |
clHandles' <- forM recipients $
|
1382
|
50 |
\ch -> Control.Exception.handle (\e -> putStrLn (show e) >> hClose ch >> return []) $ -- cannot just remove
|
1370
|
51 |
do
|
|
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
|
|
61 |
remove list rmClHandles = deleteFirstsBy2t (\ a b -> (Miscutils.handle a) == b) list rmClHandles
|
|
62 |
|
|
63 |
|
|
64 |
mainLoop :: Socket -> TChan ClientInfo -> [ClientInfo] -> [RoomInfo] -> IO ()
|
|
65 |
mainLoop servSock acceptChan clients rooms = do
|
|
66 |
r <- atomically $ (Left `fmap` readTChan acceptChan) `orElse` (Right `fmap` tselect clients)
|
|
67 |
case r of
|
|
68 |
Left ci -> do
|
|
69 |
mainLoop servSock acceptChan (clients ++ [ci]) rooms
|
|
70 |
Right (cmd, client) -> do
|
|
71 |
putStrLn ("> " ++ show cmd)
|
|
72 |
|
|
73 |
let (clientsFunc, roomsFunc, answers) = handleCmd client clients rooms $ cmd
|
|
74 |
let mrooms = roomsFunc rooms
|
|
75 |
let mclients = (clientsFunc clients)
|
|
76 |
let mclient = fromMaybe client $ find (== client) mclients
|
|
77 |
|
|
78 |
clientsIn <- sendAnswers answers mclient mclients mrooms
|
|
79 |
|
1385
|
80 |
let hadRooms = (not $ null rooms) && (null mrooms)
|
|
81 |
in unless ((not $ isDedicated globalOptions) && ((null clientsIn) || hadRooms)) $
|
|
82 |
mainLoop servSock acceptChan clientsIn mrooms
|
1370
|
83 |
|
|
84 |
|
|
85 |
startServer serverSocket = do
|
|
86 |
acceptChan <- atomically newTChan
|
|
87 |
forkIO $ acceptLoop serverSocket acceptChan
|
|
88 |
mainLoop serverSocket acceptChan [] []
|
|
89 |
|
|
90 |
|
|
91 |
main = withSocketsDo $ do
|
1383
|
92 |
putStrLn $ "Listening on port " ++ show (listenPort globalOptions)
|
|
93 |
serverSocket <- listenOn $ PortNumber (listenPort globalOptions)
|
1370
|
94 |
startServer serverSocket `finally` sClose serverSocket
|