author | unc0rr |
Fri, 07 Nov 2008 16:33:23 +0000 | |
changeset 1480 | aec44e91f2d1 |
parent 1478 | 8bfb417d165e |
child 1481 | f741afa7dbf3 |
permissions | -rw-r--r-- |
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) |
|
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
9 |
import Control.Monad |
1391 | 10 |
import Maybe (fromMaybe, isJust, fromJust) |
1370 | 11 |
import Data.List |
12 |
import Miscutils |
|
13 |
import HWProto |
|
14 |
import Opts |
|
1478 | 15 |
import Data.Time |
1397 | 16 |
|
1398 | 17 |
#if !defined(mingw32_HOST_OS) |
1396 | 18 |
import System.Posix |
1397 | 19 |
#endif |
20 |
||
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
21 |
data Messages = |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
22 |
Accept ClientInfo |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
23 |
| ClientMessage ([String], ClientInfo) |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
24 |
| CoreMessage [String] |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
25 |
|
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
26 |
messagesLoop :: TChan [String] -> IO() |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
27 |
messagesLoop messagesChan = forever $ do |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
28 |
threadDelay (30 * 10^6) -- 30 seconds |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
29 |
atomically $ writeTChan messagesChan ["PING"] |
1370 | 30 |
|
31 |
acceptLoop :: Socket -> TChan ClientInfo -> IO () |
|
1469 | 32 |
acceptLoop servSock acceptChan = Control.Exception.handle (const $ putStrLn "exception on connect" >> acceptLoop servSock acceptChan) $ do |
1478 | 33 |
(cHandle, host, _) <- accept servSock |
34 |
putStrLn $ "new client: " ++ host |
|
35 |
currentTime <- getCurrentTime |
|
1370 | 36 |
cChan <- atomically newTChan |
37 |
forkIO $ clientLoop cHandle cChan |
|
1478 | 38 |
atomically $ writeTChan acceptChan (ClientInfo cChan cHandle host currentTime"" 0 "" False False False) |
1469 | 39 |
atomically $ writeTChan cChan ["ASKME"] |
1370 | 40 |
acceptLoop servSock acceptChan |
41 |
||
42 |
||
43 |
listenLoop :: Handle -> [String] -> TChan [String] -> IO () |
|
44 |
listenLoop handle buf chan = do |
|
45 |
str <- hGetLine handle |
|
46 |
if str == "" then do |
|
47 |
atomically $ writeTChan chan buf |
|
48 |
listenLoop handle [] chan |
|
49 |
else |
|
50 |
listenLoop handle (buf ++ [str]) chan |
|
51 |
||
52 |
||
53 |
clientLoop :: Handle -> TChan [String] -> IO () |
|
54 |
clientLoop handle chan = |
|
55 |
listenLoop handle [] chan |
|
1478 | 56 |
`catch` (\e -> (clientOff $ show e) >> return ()) |
57 |
where clientOff msg = atomically $ writeTChan chan ["QUIT", msg] -- if the client disconnects, we perform as if it sent QUIT message |
|
1370 | 58 |
|
59 |
||
60 |
sendAnswers [] _ clients _ = return clients |
|
61 |
sendAnswers ((handlesFunc, answer):answers) client clients rooms = do |
|
62 |
let recipients = handlesFunc client clients rooms |
|
1476 | 63 |
--unless (null recipients) $ putStrLn ("< " ++ (show answer)) |
1478 | 64 |
when (head answer == "NICK") $ putStrLn (show answer) |
1370 | 65 |
|
66 |
clHandles' <- forM recipients $ |
|
1468 | 67 |
\ch -> Control.Exception.handle |
1478 | 68 |
(\e -> if head answer == "BYE" then |
1468 | 69 |
return [ch] |
70 |
else |
|
1478 | 71 |
atomically $ writeTChan (chan $ fromJust $ clientByHandle ch clients) ["QUIT", show e] >> return [] -- cannot just remove |
1468 | 72 |
) $ |
1370 | 73 |
do |
74 |
forM_ answer (\str -> hPutStrLn ch str) |
|
75 |
hPutStrLn ch "" |
|
76 |
hFlush ch |
|
1466 | 77 |
if head answer == "BYE" then return [ch] else return [] |
1370 | 78 |
|
1476 | 79 |
let outHandles = concat clHandles' |
1478 | 80 |
unless (null outHandles) $ putStrLn ((show $ length outHandles) ++ " / " ++ (show $ length clients) ++ " : " ++ (show answer)) |
1476 | 81 |
mapM_ (\ch -> Control.Exception.handle (const $ putStrLn "error on hClose") (hClose ch)) outHandles |
82 |
let mclients = remove clients outHandles |
|
1370 | 83 |
|
84 |
sendAnswers answers client mclients rooms |
|
85 |
where |
|
86 |
remove list rmClHandles = deleteFirstsBy2t (\ a b -> (Miscutils.handle a) == b) list rmClHandles |
|
87 |
||
88 |
||
1391 | 89 |
reactCmd :: [String] -> ClientInfo -> [ClientInfo] -> [RoomInfo] -> IO ([ClientInfo], [RoomInfo]) |
90 |
reactCmd cmd client clients rooms = do |
|
1473 | 91 |
--putStrLn ("> " ++ show cmd) |
1391 | 92 |
|
93 |
let (clientsFunc, roomsFunc, answers) = handleCmd client clients rooms $ cmd |
|
94 |
let mrooms = roomsFunc rooms |
|
95 |
let mclients = (clientsFunc clients) |
|
96 |
let mclient = fromMaybe client $ find (== client) mclients |
|
97 |
||
98 |
clientsIn <- sendAnswers answers mclient mclients mrooms |
|
99 |
let quitClient = find forceQuit $ clientsIn |
|
1474 | 100 |
|
1473 | 101 |
if isJust quitClient then |
1478 | 102 |
reactCmd ["QUIT", "Kicked"] (fromJust quitClient) clientsIn mrooms |
1474 | 103 |
else |
1473 | 104 |
return (clientsIn, mrooms) |
1391 | 105 |
|
106 |
||
1480 | 107 |
mainLoop :: TChan ClientInfo -> TChan [String] -> [ClientInfo] -> [RoomInfo] -> IO () |
108 |
mainLoop acceptChan messagesChan clients rooms = do |
|
1473 | 109 |
r <- atomically $ |
110 |
(Accept `fmap` readTChan acceptChan) `orElse` |
|
111 |
(ClientMessage `fmap` tselect clients) `orElse` |
|
112 |
(CoreMessage `fmap` readTChan messagesChan) |
|
1370 | 113 |
case r of |
1478 | 114 |
Accept ci -> do |
115 |
let sameHostClients = filter (\cl -> host ci == host cl) clients |
|
116 |
let haveJustConnected = not $ null $ filter (\cl -> diffUTCTime (connectTime ci) (connectTime cl) <= 5) sameHostClients |
|
117 |
||
118 |
when haveJustConnected $ do |
|
119 |
atomically $ writeTChan (chan ci) ["QUIT", "Reconnected too fast"] |
|
1480 | 120 |
mainLoop acceptChan messagesChan (clients ++ [ci]) rooms |
1478 | 121 |
|
1480 | 122 |
mainLoop acceptChan messagesChan (clients ++ [ci]) rooms |
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
123 |
ClientMessage (cmd, client) -> do |
1391 | 124 |
(clientsIn, mrooms) <- reactCmd cmd client clients rooms |
1370 | 125 |
|
1385 | 126 |
let hadRooms = (not $ null rooms) && (null mrooms) |
127 |
in unless ((not $ isDedicated globalOptions) && ((null clientsIn) || hadRooms)) $ |
|
1480 | 128 |
mainLoop acceptChan messagesChan clientsIn mrooms |
1473 | 129 |
CoreMessage msg -> |
130 |
if not $ null $ clients then |
|
131 |
do |
|
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
132 |
let client = head clients -- don't care |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
133 |
(clientsIn, mrooms) <- reactCmd msg client clients rooms |
1480 | 134 |
mainLoop acceptChan messagesChan clientsIn mrooms |
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
135 |
else |
1480 | 136 |
mainLoop acceptChan messagesChan clients rooms |
1370 | 137 |
|
1480 | 138 |
startServer :: Socket -> IO() |
1370 | 139 |
startServer serverSocket = do |
140 |
acceptChan <- atomically newTChan |
|
141 |
forkIO $ acceptLoop serverSocket acceptChan |
|
1461
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
142 |
|
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
143 |
messagesChan <- atomically newTChan |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
144 |
forkIO $ messagesLoop messagesChan |
87e5a6c3882c
Ping clients every 30 seconds, should help with ghosts on server
unc0rr
parents:
1403
diff
changeset
|
145 |
|
1480 | 146 |
mainLoop acceptChan messagesChan [] [] |
1370 | 147 |
|
148 |
||
149 |
main = withSocketsDo $ do |
|
1398 | 150 |
#if !defined(mingw32_HOST_OS) |
1396 | 151 |
installHandler sigPIPE Ignore Nothing; |
1397 | 152 |
#endif |
1383 | 153 |
putStrLn $ "Listening on port " ++ show (listenPort globalOptions) |
154 |
serverSocket <- listenOn $ PortNumber (listenPort globalOptions) |
|
1370 | 155 |
startServer serverSocket `finally` sClose serverSocket |