Use PublicGame returned by the player and stop keeping track of the game's state internally
This commit is contained in:
parent
8147589377
commit
d1eb8e957e
3 changed files with 75 additions and 32 deletions
|
@ -62,18 +62,17 @@ receive (Session.Answering to) message@(Message.Answer {Message.accept}) = do
|
||||||
setSessionStatus newStatus
|
setSessionStatus newStatus
|
||||||
_ -> sendError "They're not waiting for your answer"
|
_ -> sendError "They're not waiting for your answer"
|
||||||
|
|
||||||
receive (Session.Playing gameID) played@(Message.Play {}) = do
|
receive (Session.Playing gameID) (Message.Play {Message.move, Message.onGame}) = do
|
||||||
playerID <- asks App.playerID
|
playerID <- asks App.playerID
|
||||||
game <- Server.get gameID <$> App.server
|
result <- Game.play playerID move onGame
|
||||||
(result, logs) <- Game.play playerID (Message.move played) game
|
|
||||||
case result of
|
case result of
|
||||||
Left message -> sendError message
|
Left message -> sendError message
|
||||||
Right newGame -> do
|
Right (newGame, logs) -> do
|
||||||
case KoiKoi.step newGame of
|
case KoiKoi.step newGame of
|
||||||
KoiKoi.Over -> do
|
KoiKoi.Over -> do
|
||||||
App.debug $ "Game " ++ show gameID ++ " ended"
|
App.debug $ "Game " ++ show gameID ++ " ended"
|
||||||
App.update_ $ Server.endGame gameID
|
App.update_ $ Server.endGame gameID
|
||||||
_ -> App.update_ $ Server.update gameID (const newGame)
|
_ -> return ()
|
||||||
Messaging.notifyPlayers newGame logs
|
Messaging.notifyPlayers newGame logs
|
||||||
|
|
||||||
receive (Session.Playing gameID) Message.Quit = do
|
receive (Session.Playing gameID) Message.Quit = do
|
||||||
|
|
94
src/Game.hs
94
src/Game.hs
|
@ -1,29 +1,30 @@
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
module Game (
|
module Game (
|
||||||
export
|
exportGame
|
||||||
, new
|
, new
|
||||||
, play
|
, play
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified App (T, server, update)
|
import qualified App (T, server, update)
|
||||||
import Control.Monad.Except (runExceptT, throwError)
|
import Control.Monad.Except (runExceptT)
|
||||||
import Control.Monad.Reader (lift)
|
import Control.Monad.Reader (lift)
|
||||||
import Control.Monad.Writer (runWriterT)
|
import Control.Monad.Writer (runWriterT)
|
||||||
import qualified Crypto.Saltine.Class as Saltine (IsEncoding(..))
|
import qualified Crypto.Saltine.Class as Saltine (IsEncoding(..))
|
||||||
import Crypto.Saltine.Core.SecretBox (newNonce, secretbox)
|
import Crypto.Saltine.Core.SecretBox (newNonce, secretbox, secretboxOpen)
|
||||||
import Crypto.Saltine.Core.Sign (signDetached)
|
import Crypto.Saltine.Core.Sign (signDetached, signVerifyDetached)
|
||||||
import Data.Aeson (ToJSON, encode)
|
import Data.Aeson (ToJSON, eitherDecode', encode)
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import Data.ByteString.Lazy (toStrict)
|
import Data.ByteString.Lazy (fromStrict, toStrict)
|
||||||
import Data.Map (Map)
|
import Data.Map ((!), Map, mapWithKey)
|
||||||
import qualified Hanafuda (Pack)
|
import qualified Hanafuda (Pack)
|
||||||
import Hanafuda.KoiKoi (Game, GameID, Mode(..), Player, PlayerID, Players)
|
import Hanafuda.KoiKoi (Game, GameID, Mode(..), Player, PlayerID, Players)
|
||||||
import qualified Hanafuda.KoiKoi as KoiKoi (
|
import qualified Hanafuda.KoiKoi as KoiKoi (
|
||||||
Action, Game(..), Move(..), play, new
|
Action, Game(..), Move(..), play, new
|
||||||
)
|
)
|
||||||
import Hanafuda.Message (PrivateState(..), PublicGame(..), PublicPlayer(..), PublicState(..))
|
import Hanafuda.Message (PrivateState(..), PublicGame(..), PublicPlayer(..), PublicState(..))
|
||||||
import qualified Hanafuda.Player as Player (Player(..), Players(..), get, next)
|
import qualified Hanafuda.Player as Player (Player(..), Players(..), get)
|
||||||
import Keys (T(..), secret)
|
import Keys (T(..))
|
||||||
|
import qualified Keys (public, secret)
|
||||||
import qualified Server (T(..), register)
|
import qualified Server (T(..), register)
|
||||||
|
|
||||||
new :: (PlayerID, PlayerID) -> App.T GameID
|
new :: (PlayerID, PlayerID) -> App.T GameID
|
||||||
|
@ -35,14 +36,13 @@ exportPlayers game =
|
||||||
let (Player.Players players) = KoiKoi.players game in
|
let (Player.Players players) = KoiKoi.players game in
|
||||||
players
|
players
|
||||||
|
|
||||||
privateState :: PlayerID -> Game -> PrivateState
|
privateState :: Game -> PrivateState
|
||||||
privateState playerID game = PrivateState {
|
privateState game = PrivateState {
|
||||||
opponentHand = getHand opponentID players
|
hands = Player.hand <$> players
|
||||||
, deck = KoiKoi.deck game
|
, deck = KoiKoi.deck game
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
players = KoiKoi.players game
|
Player.Players players = KoiKoi.players game
|
||||||
opponentID = Player.next players playerID
|
|
||||||
|
|
||||||
getHand :: PlayerID -> Players -> Hanafuda.Pack
|
getHand :: PlayerID -> Players -> Hanafuda.Pack
|
||||||
getHand playerID = Player.hand . (Player.get playerID)
|
getHand playerID = Player.hand . (Player.get playerID)
|
||||||
|
@ -53,11 +53,19 @@ publicPlayer player = PublicPlayer {
|
||||||
, yakus = Player.yakus player
|
, yakus = Player.yakus player
|
||||||
}
|
}
|
||||||
|
|
||||||
|
privatePlayer :: Map PlayerID PublicPlayer -> PlayerID -> Hanafuda.Pack -> Player
|
||||||
|
privatePlayer publicPlayers playerID hand = Player.Player {
|
||||||
|
Player.hand
|
||||||
|
, Player.meld = meld (publicPlayers ! playerID)
|
||||||
|
, Player.yakus = yakus (publicPlayers ! playerID)
|
||||||
|
}
|
||||||
|
|
||||||
publicState :: Game -> PublicState
|
publicState :: Game -> PublicState
|
||||||
publicState game = PublicState {
|
publicState game = PublicState {
|
||||||
mode = KoiKoi.mode game
|
mode = KoiKoi.mode game
|
||||||
, scores = KoiKoi.scores game
|
, scores = KoiKoi.scores game
|
||||||
, month = KoiKoi.month game
|
, month = KoiKoi.month game
|
||||||
|
, nextPlayer = KoiKoi.nextPlayer game
|
||||||
, players = publicPlayer <$> exportPlayers game
|
, players = publicPlayer <$> exportPlayers game
|
||||||
, playing = KoiKoi.playing game
|
, playing = KoiKoi.playing game
|
||||||
, winning = KoiKoi.winning game
|
, winning = KoiKoi.winning game
|
||||||
|
@ -69,8 +77,8 @@ publicState game = PublicState {
|
||||||
, rounds = KoiKoi.rounds game
|
, rounds = KoiKoi.rounds game
|
||||||
}
|
}
|
||||||
|
|
||||||
export :: PlayerID -> Game -> App.T PublicGame
|
exportGame :: PlayerID -> Game -> App.T PublicGame
|
||||||
export playerID game = do
|
exportGame playerID game = do
|
||||||
Keys.T {encrypt, sign} <- Server.keys <$> App.server
|
Keys.T {encrypt, sign} <- Server.keys <$> App.server
|
||||||
n <- lift newNonce
|
n <- lift newNonce
|
||||||
return $ PublicGame {
|
return $ PublicGame {
|
||||||
|
@ -78,16 +86,52 @@ export playerID game = do
|
||||||
, playerHand = getHand playerID (KoiKoi.players game)
|
, playerHand = getHand playerID (KoiKoi.players game)
|
||||||
, private = secretbox encrypt n $ toJSON private
|
, private = secretbox encrypt n $ toJSON private
|
||||||
, public
|
, public
|
||||||
, publicSignature = signDetached (secret sign) $ toJSON public
|
, publicSignature = signDetached (Keys.secret sign) $ toJSON public
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
public = publicState game
|
public = publicState game
|
||||||
private = privateState playerID game
|
private = privateState game
|
||||||
toJSON :: ToJSON a => a -> ByteString
|
|
||||||
toJSON = toStrict . encode
|
|
||||||
|
|
||||||
play :: PlayerID -> KoiKoi.Move -> Game -> App.T (Either String Game, [KoiKoi.Action])
|
toJSON :: ToJSON a => a -> ByteString
|
||||||
play playerID move game = lift . runWriterT . runExceptT $
|
toJSON = toStrict . encode
|
||||||
if KoiKoi.playing game == playerID
|
|
||||||
then KoiKoi.play move game
|
gameOf :: PublicState -> PrivateState -> Game
|
||||||
else throwError "Not your turn"
|
gameOf public private = KoiKoi.Game {
|
||||||
|
KoiKoi.mode = mode public
|
||||||
|
, KoiKoi.scores = scores public
|
||||||
|
, KoiKoi.month = month public
|
||||||
|
, KoiKoi.nextPlayer = nextPlayer public
|
||||||
|
, KoiKoi.players = Player.Players $
|
||||||
|
mapWithKey (privatePlayer $ players public) (hands private)
|
||||||
|
, KoiKoi.playing = playing public
|
||||||
|
, KoiKoi.winning = winning public
|
||||||
|
, KoiKoi.oyake = winning public
|
||||||
|
, KoiKoi.deck = deck private
|
||||||
|
, KoiKoi.river = river public
|
||||||
|
, KoiKoi.step = step public
|
||||||
|
, KoiKoi.trick = trick public
|
||||||
|
, KoiKoi.rounds = rounds public
|
||||||
|
}
|
||||||
|
|
||||||
|
importGame :: PublicGame -> App.T (Either String Game)
|
||||||
|
importGame PublicGame {nonce, private, public, publicSignature} = do
|
||||||
|
Keys.T {encrypt, sign} <- Server.keys <$> App.server
|
||||||
|
if signVerifyDetached (Keys.public sign) publicSignature $ toJSON public
|
||||||
|
then return $ do
|
||||||
|
n <- Saltine.decode nonce `orDie` "Could not decode nonce"
|
||||||
|
decrypted <- secretboxOpen encrypt n private
|
||||||
|
`orDie` "Could not decrypt private state"
|
||||||
|
gameOf public <$> eitherDecode' (fromStrict decrypted)
|
||||||
|
else return $ Left "The game state has been tampered with"
|
||||||
|
where
|
||||||
|
orDie :: Maybe a -> String -> Either String a
|
||||||
|
orDie m errorMessage = maybe (Left errorMessage) Right m
|
||||||
|
|
||||||
|
play :: PlayerID -> KoiKoi.Move -> PublicGame -> App.T (Either String (Game, [KoiKoi.Action]))
|
||||||
|
play playerID move publicGame
|
||||||
|
| playing (public publicGame) == playerID = do
|
||||||
|
imported <- importGame publicGame
|
||||||
|
case imported of
|
||||||
|
Left errorMessage -> return $ Left errorMessage
|
||||||
|
Right game -> lift . runExceptT . runWriterT $ KoiKoi.play move game
|
||||||
|
| otherwise = return $ Left "Not your turn"
|
||||||
|
|
|
@ -24,7 +24,7 @@ import qualified Hanafuda.KoiKoi as KoiKoi (Action, Game(..), PlayerID)
|
||||||
import Hanafuda.Message (FromClient(..), T(..))
|
import Hanafuda.Message (FromClient(..), T(..))
|
||||||
import qualified Hanafuda.Message as Message (T)
|
import qualified Hanafuda.Message as Message (T)
|
||||||
import Network.WebSockets (receiveData, sendTextData)
|
import Network.WebSockets (receiveData, sendTextData)
|
||||||
import qualified Game (export)
|
import qualified Game (exportGame)
|
||||||
import qualified Server (T(..), get)
|
import qualified Server (T(..), get)
|
||||||
import qualified Session (T(..))
|
import qualified Session (T(..))
|
||||||
|
|
||||||
|
@ -73,5 +73,5 @@ update = Update {alone = [], paired = []}
|
||||||
notifyPlayers :: KoiKoi.Game -> [KoiKoi.Action] -> App.T ()
|
notifyPlayers :: KoiKoi.Game -> [KoiKoi.Action] -> App.T ()
|
||||||
notifyPlayers game logs =
|
notifyPlayers game logs =
|
||||||
forM_ (keys $ KoiKoi.scores game) $ \k -> do
|
forM_ (keys $ KoiKoi.scores game) $ \k -> do
|
||||||
state <- Game.export k game
|
state <- Game.exportGame k game
|
||||||
sendTo [k] $ Game {state, logs}
|
sendTo [k] $ Game {state, logs}
|
||||||
|
|
Loading…
Add table
Reference in a new issue