--- a/gameServer/Actions.hs Fri Sep 30 11:00:48 2011 +0200
+++ b/gameServer/Actions.hs Tue Sep 27 19:27:19 2011 +0400
@@ -27,6 +27,7 @@
import ServerState
import Consts
import ConfigFile
+import EngineInteraction
data Action =
AnswerClients ![ClientChan] ![B.ByteString]
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/gameServer/EngineInteraction.hs Tue Sep 27 19:27:19 2011 +0400
@@ -0,0 +1,32 @@
+module EngineInteraction where
+
+import qualified Data.Set as Set
+import qualified Data.List as List
+import Control.Monad
+import qualified Codec.Binary.Base64 as Base64
+import qualified Data.ByteString.Char8 as B
+import qualified Data.ByteString as BW
+
+
+
+toEngineMsg :: B.ByteString -> B.ByteString
+toEngineMsg msg = B.pack $ Base64.encode (fromIntegral (BW.length msg) : BW.unpack msg)
+
+
+fromEngineMsg :: B.ByteString -> Maybe B.ByteString
+fromEngineMsg msg = liftM BW.pack (Base64.decode (B.unpack msg) >>= removeLength)
+ where
+ removeLength (x:xs) = if length xs == fromIntegral x then Just xs else Nothing
+ removeLength _ = Nothing
+
+
+checkNetCmd :: B.ByteString -> (Bool, Bool)
+checkNetCmd msg = check decoded
+ where
+ decoded = fromEngineMsg msg
+ check Nothing = (False, False)
+ check (Just ms) | B.length ms > 0 = let m = B.head ms in (m `Set.member` legalMessages, m == '+')
+ | otherwise = (False, False)
+ legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,sFNpPwtghbc12345" ++ slotMessages
+ slotMessages = "\128\129\130\131\132\133\134\135\136\137\138"
+
--- a/gameServer/HWProtoInRoomState.hs Fri Sep 30 11:00:48 2011 +0200
+++ b/gameServer/HWProtoInRoomState.hs Tue Sep 27 19:27:19 2011 +0400
@@ -14,6 +14,7 @@
import Utils
import HandlerUtils
import RoomsAndClients
+import EngineInteraction
handleCmd_inRoom :: CmdHandler
--- a/gameServer/HWProtoLobbyState.hs Fri Sep 30 11:00:48 2011 +0200
+++ b/gameServer/HWProtoLobbyState.hs Tue Sep 27 19:27:19 2011 +0400
@@ -12,6 +12,7 @@
import Utils
import HandlerUtils
import RoomsAndClients
+import EngineInteraction
answerAllTeams :: ClientInfo -> [TeamInfo] -> [Action]
--- a/gameServer/Utils.hs Fri Sep 30 11:00:48 2011 +0200
+++ b/gameServer/Utils.hs Tue Sep 27 19:27:19 2011 +0400
@@ -26,25 +26,6 @@
$ List.intersperse (':':)
$ concatMap (\n -> (\(a0, a1) -> [showHex a0, showHex a1]) $ divMod n 65536) [a, b, c, d]) []
-toEngineMsg :: B.ByteString -> B.ByteString
-toEngineMsg msg = B.pack $ Base64.encode (fromIntegral (BW.length msg) : BW.unpack msg)
-
-fromEngineMsg :: B.ByteString -> Maybe B.ByteString
-fromEngineMsg msg = liftM BW.pack (Base64.decode (B.unpack msg) >>= removeLength)
- where
- removeLength (x:xs) = if length xs == fromIntegral x then Just xs else Nothing
- removeLength _ = Nothing
-
-checkNetCmd :: B.ByteString -> (Bool, Bool)
-checkNetCmd msg = check decoded
- where
- decoded = fromEngineMsg msg
- check Nothing = (False, False)
- check (Just ms) | B.length ms > 0 = let m = B.head ms in (m `Set.member` legalMessages, m == '+')
- | otherwise = (False, False)
- legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,sFNpPwtghbc12345" ++ slotMessages
- slotMessages = "\128\129\130\131\132\133\134\135\136\137\138"
-
maybeRead :: Read a => String -> Maybe a
maybeRead s = case reads s of
[(x, rest)] | all isSpace rest -> Just x