gameServer/HandlerUtils.hs
branchserver_refactor
changeset 4614 26661bf28dd5
parent 3568 ae89cf0735dc
child 4932 f11d80bac7ed
equal deleted inserted replaced
4612:e82758d6f924 4614:26661bf28dd5
     1 module HandlerUtils where
     1 module HandlerUtils where
     2 
     2 
     3 import Control.Monad.Reader
     3 import Control.Monad.Reader
     4 import qualified Data.ByteString.Char8 as B
     4 import qualified Data.ByteString.Char8 as B
       
     5 import Data.List
     5 
     6 
     6 import RoomsAndClients
     7 import RoomsAndClients
     7 import CoreTypes
     8 import CoreTypes
     8 import Actions
     9 import Actions
     9 
    10 
    25 roomOthersChans = do
    26 roomOthersChans = do
    26     (ci, rnc) <- ask
    27     (ci, rnc) <- ask
    27     let ri = clientRoom rnc ci
    28     let ri = clientRoom rnc ci
    28     return $ map (sendChan . client rnc) $ filter (/= ci) (roomClients rnc ri)
    29     return $ map (sendChan . client rnc) $ filter (/= ci) (roomClients rnc ri)
    29 
    30 
       
    31 roomSameClanChans :: Reader (ClientIndex, IRnC) [ClientChan]
       
    32 roomSameClanChans = do
       
    33     (ci, rnc) <- ask
       
    34     let ri = clientRoom rnc ci
       
    35     let otherRoomClients = map (client rnc) . filter (/= ci) $ roomClients rnc ri
       
    36     let cl = rnc `client` ci
       
    37     let thisClan = clientClan cl
       
    38     let sameClanClients = Prelude.filter (\c -> teamsInGame cl > 0 && clientClan c == thisClan) otherRoomClients
       
    39     let spectators = Prelude.filter (\c -> teamsInGame c == 0) otherRoomClients
       
    40     let sameClanOrSpec = if teamsInGame cl > 0 then sameClanClients else spectators
       
    41     return $ map sendChan sameClanOrSpec
       
    42 
    30 roomClientsChans :: Reader (ClientIndex, IRnC) [ClientChan]
    43 roomClientsChans :: Reader (ClientIndex, IRnC) [ClientChan]
    31 roomClientsChans = do
    44 roomClientsChans = do
    32     (ci, rnc) <- ask
    45     (ci, rnc) <- ask
    33     let ri = clientRoom rnc ci
    46     let ri = clientRoom rnc ci
    34     return $ map (sendChan . client rnc) (roomClients rnc ri)
    47     return $ map (sendChan . client rnc) (roomClients rnc ri)
    41 answerClient :: [B.ByteString] -> Reader (ClientIndex, IRnC) [Action]
    54 answerClient :: [B.ByteString] -> Reader (ClientIndex, IRnC) [Action]
    42 answerClient msg = thisClientChans >>= return . (: []) . flip AnswerClients msg
    55 answerClient msg = thisClientChans >>= return . (: []) . flip AnswerClients msg
    43 
    56 
    44 allRoomInfos :: Reader (a, IRnC) [RoomInfo]
    57 allRoomInfos :: Reader (a, IRnC) [RoomInfo]
    45 allRoomInfos = liftM ((\irnc -> map (room irnc) $ allRooms irnc) . snd) ask
    58 allRoomInfos = liftM ((\irnc -> map (room irnc) $ allRooms irnc) . snd) ask
       
    59 
       
    60 clientByNick :: B.ByteString -> Reader (ClientIndex, IRnC) (Maybe ClientIndex)
       
    61 clientByNick n = do
       
    62     (_, rnc) <- ask
       
    63     let allClientIDs = allClients rnc
       
    64     return $ find (\clId -> n == nick (client rnc clId)) allClientIDs
       
    65