Generalizing the Game type to include the public version exported to clients

This commit is contained in:
Tissevert 2019-08-18 22:08:22 +02:00
parent efddc9f07e
commit 3056974e12
4 changed files with 10 additions and 7 deletions

View File

@ -3,8 +3,9 @@
module Hanafuda.KoiKoi (
Action(..)
, Card(..)
, Game(..)
, Environment
, Game
, GameBlueprint(..)
, GameKey
, Mode(..)
, Move(..)
@ -21,7 +22,7 @@ import Hanafuda (Card(..), Flower(Pine), contains, flower, match, remove)
import qualified Hanafuda.Player as Player (players, random, scores)
import Hanafuda.KoiKoi.Yaku (Yaku(..), Score)
import Hanafuda.KoiKoi.Game (
Action(..), Environment, Game(..), GameKey, Mode(..), Move(..), PlayerKey
Action(..), Environment, Game, GameBlueprint(..), GameKey, Mode(..), Move(..), PlayerKey
, Source(..), Step(..)
)
import qualified Hanafuda.KoiKoi.Round as Round (deal, next)

View File

@ -3,8 +3,9 @@
{-# LANGUAGE ConstraintKinds #-}
module Hanafuda.KoiKoi.Game (
Action(..)
, Game(..)
, Environment
, Game
, GameBlueprint(..)
, GameKey
, Key
, Mode(..)
@ -39,7 +40,7 @@ type Environment m = (MonadIO m, MonadError String m, MonadWriter [Action] m)
type PlayerKey = Player.Key KoiKoi.Score
type GameKey = Key Game
data Game = Game {
data GameBlueprint deckType = Game {
mode :: Mode
, scores :: Scores KoiKoi.Score
, month :: Flower
@ -47,12 +48,13 @@ data Game = Game {
, playing :: PlayerKey
, winning :: PlayerKey
, oyake :: PlayerKey
, deck :: [Card]
, deck :: deckType
, river :: Pack
, step :: Step
, trick :: [Card]
, rounds :: [(PlayerKey, KoiKoi.Score)]
} deriving (Show)
type Game = GameBlueprint [Card]
setPlayer :: Game -> Player KoiKoi.Score -> Game
setPlayer game@(Game {players, playing}) player = game {players = set playing player players}

View File

@ -6,7 +6,7 @@ module Hanafuda.KoiKoi.Round (
import Hanafuda (Flower(Paulownia), cards, shuffle, packOfCards)
import Hanafuda.KoiKoi.Yaku (sumYakus)
import Hanafuda.KoiKoi.Game (Game(..), Mode(..), Step(..), end)
import Hanafuda.KoiKoi.Game (Game, GameBlueprint(..), Mode(..), Step(..), end)
import qualified Hanafuda.Player as Player (deal, get, next, score, yakus)
import Data.Map ((!), insert)
import Control.Monad.IO.Class (MonadIO)

View File

@ -11,7 +11,7 @@ import Hanafuda (Card, Pack, empty, match)
import Hanafuda.Player (Player(..), plays)
import qualified Hanafuda.Player as Player (get, next)
import Hanafuda.KoiKoi.Yaku (meldInto)
import Hanafuda.KoiKoi.Game (Action(..), Environment, Game(..), Source(..), Step(..), setPlayer)
import Hanafuda.KoiKoi.Game (Action(..), Environment, Game, GameBlueprint(..), Source(..), Step(..), setPlayer)
import qualified Hanafuda.KoiKoi.Round as Round (next)
import Control.Monad.Except (MonadError(..))
import Control.Monad.IO.Class (MonadIO)