10058
|
1 |
{-# LANGUAGE OverloadedStrings #-}
|
10049
|
2 |
module Votes where
|
|
3 |
|
|
4 |
import Control.Monad.Reader
|
10216
|
5 |
import Control.Monad.State.Strict
|
10049
|
6 |
import ServerState
|
10058
|
7 |
import qualified Data.ByteString.Char8 as B
|
10081
|
8 |
import qualified Data.List as L
|
10195
|
9 |
import qualified Data.Map as Map
|
10058
|
10 |
import Data.Maybe
|
|
11 |
-------------------
|
|
12 |
import Utils
|
|
13 |
import CoreTypes
|
|
14 |
import HandlerUtils
|
10392
|
15 |
import EngineInteraction
|
10049
|
16 |
|
10081
|
17 |
|
|
18 |
voted :: Bool -> Reader (ClientIndex, IRnC) [Action]
|
|
19 |
voted vote = do
|
|
20 |
cl <- thisClient
|
|
21 |
rm <- thisRoom
|
|
22 |
uid <- liftM clUID thisClient
|
|
23 |
|
10392
|
24 |
case voting rm of
|
|
25 |
Nothing ->
|
|
26 |
return [AnswerClients [sendChan cl] ["CHAT", "[server]", loc "There's no voting going on"]]
|
|
27 |
Just voting ->
|
|
28 |
if uid `L.notElem` entitledToVote voting then
|
|
29 |
return []
|
|
30 |
else if uid `L.elem` map fst (votes voting) then
|
|
31 |
return [AnswerClients [sendChan cl] ["CHAT", "[server]", loc "You already have voted"]]
|
|
32 |
else
|
|
33 |
actOnVoting $ voting{votes = (uid, vote):votes voting}
|
|
34 |
|
10087
|
35 |
where
|
|
36 |
actOnVoting :: Voting -> Reader (ClientIndex, IRnC) [Action]
|
|
37 |
actOnVoting vt = do
|
10212
|
38 |
let (pro, contra) = L.partition snd $ votes vt
|
10392
|
39 |
let totalV = length $ entitledToVote vt
|
|
40 |
let successV = totalV `div` 2 + 1
|
10087
|
41 |
|
10392
|
42 |
if length contra > totalV - successV then
|
10087
|
43 |
closeVoting
|
10392
|
44 |
else if length pro >= successV then do
|
10215
|
45 |
a <- act $ voteType vt
|
|
46 |
c <- closeVoting
|
|
47 |
return $ c ++ a
|
10087
|
48 |
else
|
|
49 |
return [ModifyRoom $ \r -> r{voting = Just vt}]
|
|
50 |
|
|
51 |
closeVoting = do
|
|
52 |
chans <- roomClientsChans
|
|
53 |
return [
|
|
54 |
AnswerClients chans ["CHAT", "[server]", loc "Voting closed"]
|
|
55 |
, ModifyRoom (\r -> r{voting = Nothing})
|
|
56 |
]
|
|
57 |
|
|
58 |
act (VoteKick nickname) = do
|
|
59 |
(thisClientId, rnc) <- ask
|
|
60 |
maybeClientId <- clientByNick nickname
|
|
61 |
rm <- thisRoom
|
|
62 |
let kickId = fromJust maybeClientId
|
|
63 |
let kickCl = rnc `client` kickId
|
|
64 |
let sameRoom = clientRoom rnc thisClientId == clientRoom rnc kickId
|
|
65 |
return
|
|
66 |
[KickRoomClient kickId |
|
|
67 |
isJust maybeClientId
|
|
68 |
&& sameRoom
|
|
69 |
&& ((isNothing $ gameInfo rm) || teamsInGame kickCl == 0)
|
|
70 |
]
|
10195
|
71 |
act (VoteMap roomSave) = do
|
|
72 |
rm <- thisRoom
|
|
73 |
let rs = Map.lookup roomSave (roomSaves rm)
|
|
74 |
case rs of
|
|
75 |
Nothing -> return []
|
10218
|
76 |
Just (mp, p) -> do
|
|
77 |
cl <- thisClient
|
|
78 |
chans <- roomClientsChans
|
|
79 |
let a = map (replaceChans chans) $ answerFullConfigParams cl mp p
|
|
80 |
return $
|
|
81 |
(ModifyRoom $ \r -> r{params = p, mapParams = mp})
|
|
82 |
: SendUpdateOnThisRoom
|
|
83 |
: a
|
|
84 |
where
|
|
85 |
replaceChans chans (AnswerClients _ msg) = AnswerClients chans msg
|
|
86 |
replaceChans _ a = a
|
10392
|
87 |
act (VotePause) = do
|
|
88 |
rm <- thisRoom
|
|
89 |
chans <- roomClientsChans
|
|
90 |
let modifyGameInfo f room = room{gameInfo = fmap f $ gameInfo room}
|
|
91 |
return [ModifyRoom (modifyGameInfo $ \g -> g{isPaused = not $ isPaused g}),
|
|
92 |
AnswerClients chans ["CHAT", "[server]", "Pause toggled"],
|
|
93 |
AnswerClients chans ["EM", toEngineMsg "I"]]
|
10081
|
94 |
|
10049
|
95 |
|
|
96 |
startVote :: VoteType -> Reader (ClientIndex, IRnC) [Action]
|
10058
|
97 |
startVote vt = do
|
|
98 |
(ci, rnc) <- ask
|
10090
|
99 |
--cl <- thisClient
|
10058
|
100 |
rm <- thisRoom
|
|
101 |
chans <- roomClientsChans
|
|
102 |
|
|
103 |
let uids = map (clUID . client rnc) . roomClients rnc $ clientRoom rnc ci
|
|
104 |
|
|
105 |
if isJust $ voting rm then
|
|
106 |
return []
|
|
107 |
else
|
10212
|
108 |
return [
|
|
109 |
ModifyRoom (\r -> r{voting = Just (newVoting vt){entitledToVote = uids}})
|
|
110 |
, AnswerClients chans ["CHAT", "[server]", B.concat [loc "New voting started", ": ", voteInfo vt]]
|
|
111 |
, ReactCmd ["VOTE", "YES"]
|
10215
|
112 |
]
|
10081
|
113 |
|
10049
|
114 |
|
10215
|
115 |
checkVotes :: StateT ServerState IO [Action]
|
|
116 |
checkVotes = do
|
|
117 |
rnc <- gets roomsClients
|
10216
|
118 |
liftM concat $ io $ do
|
10215
|
119 |
ris <- allRoomsM rnc
|
10216
|
120 |
mapM (check rnc) ris
|
10215
|
121 |
where
|
|
122 |
check rnc ri = do
|
|
123 |
e <- room'sM rnc voting ri
|
|
124 |
case e of
|
|
125 |
Just rv -> do
|
|
126 |
modifyRoom rnc (\r -> r{voting = if voteTTL rv == 0 then Nothing else Just rv{voteTTL = voteTTL rv - 1}}) ri
|
|
127 |
if voteTTL rv == 0 then do
|
10216
|
128 |
chans <- liftM (map sendChan) $ roomClientsM rnc ri
|
10215
|
129 |
return [AnswerClients chans ["CHAT", "[server]", loc "Voting expired"]]
|
|
130 |
else
|
|
131 |
return []
|
10216
|
132 |
Nothing -> return []
|
10058
|
133 |
|
10081
|
134 |
|
10058
|
135 |
voteInfo :: VoteType -> B.ByteString
|
|
136 |
voteInfo (VoteKick n) = B.concat [loc "kick", " ", n]
|
10195
|
137 |
voteInfo (VoteMap n) = B.concat [loc "map", " ", n]
|
10392
|
138 |
voteInfo (VotePause) = B.concat [loc "pause"]
|