- Fixed some bugs
- Introduce client protocol number field
- Handle PROTO command
--- a/netserver/HWProto.hs Wed Apr 30 20:48:12 2008 +0000
+++ b/netserver/HWProto.hs Thu May 01 14:30:12 2008 +0000
@@ -1,10 +1,44 @@
module HWProto where
import IO
+import Data.Word
import Miscutils
+import Maybe (fromMaybe)
handleCmd :: ClientInfo -> [ClientInfo] -> [RoomInfo] -> [String] -> (ClientInfo, [RoomInfo], [ClientInfo], [String])
+handleCmd_noInfo :: ClientInfo -> [ClientInfo] -> [RoomInfo] -> [String] -> (ClientInfo, [RoomInfo], [ClientInfo], [String])
+handleCmd_noRoom :: ClientInfo -> [ClientInfo] -> [RoomInfo] -> [String] -> (ClientInfo, [RoomInfo], [ClientInfo], [String])
+-- 'noInfo' clients state command handlers
+handleCmd_noInfo client clients rooms ("NICK":newNick:[]) =
+ if not . null $ nick client then
+ (client, rooms, [client], ["ERROR", "The nick already chosen"])
+ else if haveSameNick then
+ (client, rooms, [client], ["WARNING", "Choose another nick"])
+ else
+ (client{nick = newNick}, rooms, [client], ["NICK", newNick])
+ where
+ haveSameNick = not . null $ filter (\cl -> newNick == nick cl) clients
+
+handleCmd_noInfo client clients rooms ("PROTO":protoNum:[]) =
+ if protocol client > 0 then
+ (client, rooms, [client], ["ERROR", "Protocol number already known"])
+ else if parsedProto == 0 then
+ (client, rooms, [client], ["ERROR", "Bad input"])
+ else
+ (client{protocol = parsedProto}, rooms, [], [])
+ where
+ parsedProto = fromMaybe 0 (maybeRead protoNum :: Maybe Word16)
+
+
+handleCmd_noInfo client _ rooms _ = (client, rooms, [client], ["ERROR", "Bad command or incorrect parameter"])
+
+
+-- 'noRoom' clients state command handlers
+--handleCmd_noRoom client clients rooms ("CREATE":newRoom:[]) =
+
+handleCmd_noRoom client _ rooms _ = (client, rooms, [client], ["ERROR", "Bad command or incorrect parameter"])
+
handleCmd client clients rooms ("QUIT":xs) =
if null (room client) then
@@ -13,15 +47,8 @@
(client, rooms, clients, ["QUIT", nick client])
-handleCmd client clients rooms ("NICK":newNick:[]) =
- if not . null $ nick client then
- (client, rooms, [client], ["ERROR", "The nick already chosen"])
- else if haveSameNick then
- (client, rooms, [client], ["ERROR", "Choose another nick"])
+handleCmd client clients rooms cmd =
+ if null (nick client) || protocol client == 0 then
+ handleCmd_noInfo client clients rooms cmd
else
- (client{nick = newNick}, rooms, [client], ["NICK", newNick])
- where
- haveSameNick = not . null $ filter (\cl -> newNick == nick cl) clients
-
-
-handleCmd client _ rooms _ = (client, rooms, [client], ["ERROR", "Bad command"])
+ handleCmd_noRoom client clients rooms cmd
--- a/netserver/Miscutils.hs Wed Apr 30 20:48:12 2008 +0000
+++ b/netserver/Miscutils.hs Thu May 01 14:30:12 2008 +0000
@@ -5,6 +5,8 @@
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception (finally)
+import Data.Word
+import Data.Char
data ClientInfo =
ClientInfo
@@ -12,6 +14,7 @@
chan :: TChan String,
handle :: Handle,
nick :: String,
+ protocol :: Word16,
room :: String,
isMaster :: Bool
}
@@ -56,3 +59,8 @@
tselect :: [ClientInfo] -> STM (String, ClientInfo)
tselect = foldl orElse retry . map (\ci -> (flip (,) ci) `fmap` readTChan (chan ci))
+maybeRead :: Read a => String -> Maybe a
+maybeRead s = case reads s of
+ [(x, rest)] | all isSpace rest -> Just x
+ _ -> Nothing
+
--- a/netserver/newhwserv.hs Wed Apr 30 20:48:12 2008 +0000
+++ b/netserver/newhwserv.hs Thu May 01 14:30:12 2008 +0000
@@ -16,7 +16,7 @@
(cHandle, host, port) <- accept servSock
cChan <- atomically newTChan
forkIO $ clientLoop cHandle cChan
- atomically $ writeTChan acceptChan (ClientInfo cChan cHandle "" "" False)
+ atomically $ writeTChan acceptChan (ClientInfo cChan cHandle "" 0 "" False)
acceptLoop servSock acceptChan
listenLoop :: Handle -> TChan String -> IO ()
@@ -29,7 +29,6 @@
clientLoop handle chan =
listenLoop handle chan
`catch` (const $ clientOff >> return ())
- `finally` hClose handle
where clientOff = atomically $ writeTChan chan "QUIT"
mainLoop :: Socket -> TChan ClientInfo -> [ClientInfo] -> [RoomInfo] -> IO ()
@@ -48,7 +47,7 @@
return []
`catch` const (hClose (handle ci) >> return [ci])
- client' <- if head strs == "QUIT" then hClose (handle client) >> return [client] else return []
+ client' <- if (not $ null strs) && (head strs == "QUIT") then hClose (handle client) >> return [client] else return []
mainLoop servSock acceptChan (remove (remove (mclient : filter (\cl -> handle cl /= handle client) clients) (concat clients')) client') mrooms
where