gameServer/HWProtoNEState.hs
changeset 4904 0eab727d4717
parent 4862 899b4e3d350a
parent 4610 9541b2a76067
child 4932 f11d80bac7ed
--- a/gameServer/HWProtoNEState.hs	Wed Feb 02 09:05:48 2011 +0100
+++ b/gameServer/HWProtoNEState.hs	Wed Feb 02 11:28:38 2011 +0300
@@ -1,54 +1,61 @@
+{-# LANGUAGE OverloadedStrings #-}
 module HWProtoNEState where
 
 import qualified Data.IntMap as IntMap
 import Data.Maybe
 import Data.List
 import Data.Word
+import Control.Monad.Reader
+import qualified Data.ByteString.Char8 as B
 --------------------------------------
 import CoreTypes
 import Actions
 import Utils
+import RoomsAndClients
 
 handleCmd_NotEntered :: CmdHandler
 
-handleCmd_NotEntered clID clients _ ["NICK", newNick]
-    | not . null $ nick client = [ProtocolError "Nickname already chosen"]
-    | haveSameNick = [AnswerThisClient ["WARNING", "Nickname already in use"], ByeClient "Nickname already in use"]
-    | illegalName newNick = [ByeClient "Illegal nickname"]
-    | otherwise =
-        ModifyClient (\c -> c{nick = newNick}) :
-        AnswerThisClient ["NICK", newNick] :
-        [CheckRegistered | clientProto client /= 0]
+handleCmd_NotEntered ["NICK", newNick] = do
+    (ci, irnc) <- ask
+    let cl = irnc `client` ci
+    if not . B.null $ nick cl then return [ProtocolError "Nickname already chosen"]
+        else
+        if haveSameNick irnc then return [NoticeMessage NickAlreadyInUse]
+            else
+            if illegalName newNick then return [ByeClient "Illegal nickname"]
+                else
+                return $
+                    ModifyClient (\c -> c{nick = newNick}) :
+                    AnswerClients [sendChan cl] ["NICK", newNick] :
+                    [CheckRegistered | clientProto cl /= 0]
     where
-        client = clients IntMap.! clID
-        haveSameNick = isJust $ find (\cl -> newNick == nick cl) $ IntMap.elems clients
+    haveSameNick irnc = isJust . find (== newNick) . map (nick . client irnc) $ allClients irnc
+
+handleCmd_NotEntered ["PROTO", protoNum] = do
+    (ci, irnc) <- ask
+    let cl = irnc `client` ci
+    if clientProto cl > 0 then return [ProtocolError "Protocol already known"]
+        else
+        if parsedProto == 0 then return [ProtocolError "Bad number"]
+            else
+            return $
+                ModifyClient (\c -> c{clientProto = parsedProto}) :
+                AnswerClients [sendChan cl] ["PROTO", B.pack $ show parsedProto] :
+                [CheckRegistered | not . B.null $ nick cl]
+    where
+        parsedProto = case B.readInt protoNum of
+                           Just (i, t) | B.null t -> fromIntegral i
+                           otherwise -> 0
 
 
-handleCmd_NotEntered clID clients _ ["PROTO", protoNum]
-    | clientProto client > 0 = [ProtocolError "Protocol already known"]
-    | parsedProto == 0 = [ProtocolError "Bad number"]
-    | otherwise =
-        ModifyClient (\c -> c{clientProto = parsedProto}) :
-        AnswerThisClient ["PROTO", show parsedProto] :
-        [CheckRegistered | (not . null) (nick client)]
-    where
-        client = clients IntMap.! clID
-        parsedProto = fromMaybe 0 (maybeRead protoNum :: Maybe Word16)
+handleCmd_NotEntered ["PASSWORD", passwd] = do
+    (ci, irnc) <- ask
+    let cl = irnc `client` ci
+
+    if passwd == webPassword cl then
+        return $ JoinLobby : [AnswerClients [sendChan cl] ["ADMIN_ACCESS"] | isAdministrator cl]
+        else
+        return [ByeClient "Authentication failed"]
 
 
-handleCmd_NotEntered clID clients _ ["PASSWORD", passwd] =
-    if passwd == webPassword client then
-        [ModifyClient (\cl -> cl{logonPassed = True}),
-        MoveToLobby] ++ adminNotice
-    else
-        [ByeClient "Authentication failed"]
-    where
-        client = clients IntMap.! clID
-        adminNotice = [AnswerThisClient ["ADMIN_ACCESS"] | isAdministrator client]
-
-
-handleCmd_NotEntered clID clients _ ["DUMP"] =
-    if isAdministrator (clients IntMap.! clID) then [Dump] else []
-
-
-handleCmd_NotEntered clID _ _ _ = [ProtocolError "Incorrect command (state: not entered)"]
+handleCmd_NotEntered _ = return [ProtocolError "Incorrect command (state: not entered)"]