Bumping to 0.3.0.0 for making the Game type signature parametric in the players' type

This commit is contained in:
Sasha 2018-07-24 22:19:04 +02:00
parent 8ad996914d
commit 4d1a2f7fee
7 changed files with 98 additions and 79 deletions

View File

@ -1,5 +1,9 @@
# Revision history for hanafuda # Revision history for hanafuda
## 0.3.0.0 -- 2018-05-28
* Make Game type parametric in the type to represent players
## 0.2.1.0 -- 2018-03-16 ## 0.2.1.0 -- 2018-03-16
* Export some more types needed to export the game's state * Export some more types needed to export the game's state

View File

@ -2,7 +2,7 @@
-- documentation, see http://haskell.org/cabal/users-guide/ -- documentation, see http://haskell.org/cabal/users-guide/
name: hanafuda name: hanafuda
version: 0.2.1.0 version: 0.3.0.0
synopsis: A game of Hanafuda (a family of japanese card games) synopsis: A game of Hanafuda (a family of japanese card games)
description: This is a library to represent the cards and the players description: This is a library to represent the cards and the players
of games in this family. It also implements one such game of games in this family. It also implements one such game
@ -37,7 +37,7 @@ library
, Hanafuda.KoiKoi.Yaku , Hanafuda.KoiKoi.Yaku
-- other-modules: -- other-modules:
-- other-extensions: -- other-extensions:
build-depends: base >=4.10 && <4.11 build-depends: base
, containers , containers
, mtl , mtl
, random , random

View File

@ -14,14 +14,13 @@ module Hanafuda.KoiKoi (
) where ) where
import Hanafuda (Card(..), Flower(Pine), contains, flower, match, remove) import Hanafuda (Card(..), Flower(Pine), contains, flower, match, remove)
import qualified Hanafuda.Player as Player (deal) import qualified Hanafuda.Player as Player (players, random, scores)
import Hanafuda.KoiKoi.Yaku (Yaku(..), Score) import Hanafuda.KoiKoi.Yaku (Yaku(..), Score)
import Hanafuda.KoiKoi.Game (Game(..), Mode(..), Move(..), On(..), Over(..), Step(..), raise) import Hanafuda.KoiKoi.Game (Game(..), Mode(..), Move(..), On(..), Over(..), Step(..), raise)
import qualified Hanafuda.KoiKoi.Round as Round (deal, next) import qualified Hanafuda.KoiKoi.Round as Round (deal, next)
import qualified Hanafuda.KoiKoi.Turn as Turn (catch, end, next) import qualified Hanafuda.KoiKoi.Turn as Turn (catch, end, next)
import System.Random (randomIO)
play :: Move -> On -> IO Game play :: Ord player => Move -> On player -> IO (Game player)
play move on@(On_ {river, step}) = play move on@(On_ {river, step}) =
case (step, move) of case (step, move) of
(ToPlay, Play card) -> (ToPlay, Play card) ->
@ -39,19 +38,21 @@ play move on@(On_ {river, step}) =
where where
canCatch card1 card2 = flower card1 == flower card2 && river `contains` card2 canCatch card1 card2 = flower card1 == flower card2 && river `contains` card2
new :: Mode -> IO On new :: Ord player => [player] -> Mode -> IO (On player)
new mode = do new playersList mode = do
playing <- randomIO playing <- Player.random players
Round.deal $ On_ { Round.deal $ On_ {
mode mode
, scores = Player.deal [0, 0] , scores = Player.scores players [0, 0]
, month = Pine , month = Pine
, players = undefined , players
, playing , playing
, winning = playing , winning = playing
, oyake = playing , oyake = playing
, stock = undefined , deck = undefined
, river = undefined , river = undefined
, step = ToPlay , step = ToPlay
, trick = [] , trick = []
} }
where
players = Player.players playersList

View File

@ -13,41 +13,40 @@ module Hanafuda.KoiKoi.Game (
) where ) where
import Hanafuda (Card, Flower, Pack) import Hanafuda (Card, Flower, Pack)
import Hanafuda.Player (Players, Player, Scores, Seat) import Hanafuda.Player (Players, Player, Scores, set)
import Hanafuda.KoiKoi.Yaku (Score) import Hanafuda.KoiKoi.Yaku (Score)
import Data.Map (insert)
data Mode = FirstAt Int | WholeYear deriving (Show) data Mode = FirstAt Int | WholeYear deriving (Show)
data Move = Play Card | Capture (Card, Card) | Choose Card | KoiKoi Bool data Move = Play Card | Capture (Card, Card) | Choose Card | KoiKoi Bool
data Step = ToPlay | Turned Card | Scored deriving (Show) data Step = ToPlay | Turned Card | Scored deriving (Show)
data On = On_ { data On player = On_ {
mode :: Mode mode :: Mode
, scores :: Scores , scores :: Scores player
, month :: Flower , month :: Flower
, players :: Players Score , players :: Players player Score
, playing :: Seat , playing :: player
, winning :: Seat , winning :: player
, oyake :: Seat , oyake :: player
, stock :: [Card] , deck :: [Card]
, river :: Pack , river :: Pack
, step :: Step , step :: Step
, trick :: [Card] , trick :: [Card]
} deriving (Show) } deriving (Show)
data Over = Over_ { data Over player = Over_ {
finalScores :: Scores finalScores :: Scores player
} deriving (Show) } deriving (Show)
data Game = Error String | Over Over | On On deriving (Show) data Game player = Error String | Over (Over player) | On (On player) deriving (Show)
setPlayer :: On -> Player Score -> On setPlayer :: Ord player => On player -> Player player Score -> On player
setPlayer on@(On_ {players, playing}) player = on {players = insert playing player players} setPlayer on@(On_ {players, playing}) player = on {players = set playing player players}
end :: On -> IO Game end :: Ord player => On player -> IO (Game player)
end (On_ {scores}) = return . Over $ Over_ {finalScores = scores} end (On_ {scores}) = return . Over $ Over_ {finalScores = scores}
stop :: On -> IO Game stop :: Ord player => On player -> IO (Game player)
stop = return . On stop = return . On
raise :: String -> IO Game raise :: String -> IO (Game player)
raise = return . Error raise = return . Error

View File

@ -7,22 +7,22 @@ module Hanafuda.KoiKoi.Round (
import Hanafuda (Flower(Paulownia), cards, shuffle, packOfCards) import Hanafuda (Flower(Paulownia), cards, shuffle, packOfCards)
import Hanafuda.KoiKoi.Yaku (sumYakus) import Hanafuda.KoiKoi.Yaku (sumYakus)
import Hanafuda.KoiKoi.Game (Game, Mode(..), On(..), Step(..), end, stop) import Hanafuda.KoiKoi.Game (Game, Mode(..), On(..), Step(..), end, stop)
import qualified Hanafuda.Player as Player (deal, next, new, score) import qualified Hanafuda.Player as Player (deal, get, next, score)
import Data.Map ((!), insert) import Data.Map ((!), insert)
import Control.Monad.State (replicateM, runState, state) import Control.Monad.State (replicateM, runState, state)
deal :: On -> IO On deal :: Ord player => On player -> IO (On player)
deal on = do deal on@(On_ {players}) = do
([hand1, hand2, river], stock) <- fmap (runState (replicateM 3 take8)) $ shuffle cards ([hand1, hand2, river], deck) <- fmap (runState (replicateM 3 take8)) $ shuffle cards
return on { return on {
players = fmap Player.new $ Player.deal [hand1, hand2] players = Player.deal players [hand1, hand2]
, stock , deck
, river = packOfCards river , river = packOfCards river
} }
where where
take8 = state $ splitAt 8 take8 = state $ splitAt 8
next :: On -> IO Game next :: Ord player => On player -> IO (Game player)
next on@(On_ {mode, scores, month, players, oyake, winning}) = next on@(On_ {mode, scores, month, players, oyake, winning}) =
case mode of case mode of
FirstAt n | n <= newScore -> end scored FirstAt n | n <= newScore -> end scored
@ -30,8 +30,8 @@ next on@(On_ {mode, scores, month, players, oyake, winning}) =
WholeYear | month == Paulownia -> end scored WholeYear | month == Paulownia -> end scored
WholeYear -> continue WholeYear -> continue
where where
playing = Player.next oyake playing = Player.next players oyake
newScore = (scores ! winning) + Player.score sumYakus (players ! winning) newScore = (scores ! winning) + Player.score sumYakus (Player.get winning players)
scored = on {scores = insert winning newScore scores} scored = on {scores = insert winning newScore scores}
continue = continue =
deal (scored { deal (scored {

View File

@ -8,28 +8,27 @@ module Hanafuda.KoiKoi.Turn (
import Hanafuda (Card, Pack, empty, match) import Hanafuda (Card, Pack, empty, match)
import Hanafuda.Player (Player(..), plays) import Hanafuda.Player (Player(..), plays)
import qualified Hanafuda.Player as Player (next) import qualified Hanafuda.Player as Player (get, next)
import Hanafuda.KoiKoi.Yaku (meldInto) import Hanafuda.KoiKoi.Yaku (meldInto)
import Hanafuda.KoiKoi.Game (Game, On(..), Step(..), raise, setPlayer, stop) import Hanafuda.KoiKoi.Game (Game, On(..), Step(..), raise, setPlayer, stop)
import qualified Hanafuda.KoiKoi.Round as Round (next) import qualified Hanafuda.KoiKoi.Round as Round (next)
import Data.Map ((!))
import Control.Monad.Reader (runReader) import Control.Monad.Reader (runReader)
catch :: On -> Card -> (Pack, [Card]) -> IO Game catch :: Ord player => On player -> Card -> (Pack, [Card]) -> IO (Game player)
catch on@(On_ {players, playing}) card (river, trick) = catch on@(On_ {players, playing}) card (river, trick) =
either raise (popNextCard . setPlayer (on {river, trick})) played either raise (popNextCard . setPlayer (on {river, trick})) played
where where
played = (players ! playing) `plays` card played = (Player.get playing players) `plays` card
popNextCard :: On -> IO Game popNextCard :: Ord player => On player -> IO (Game player)
popNextCard (On_ {stock = []}) = raise "No more cards in the stack" popNextCard (On_ {deck = []}) = raise "No more cards in the stack"
popNextCard on@(On_ {river, stock = turned : others}) = popNextCard on@(On_ {river, deck = turned : others}) =
let pop = on {stock = others} in let pop = on {deck = others} in
case match turned river of case match turned river of
Right (newRiver, newCaptured) -> end pop (newRiver, newCaptured) Right (newRiver, newCaptured) -> end pop (newRiver, newCaptured)
Left _ -> stop $ pop {step = Turned turned} Left _ -> stop $ pop {step = Turned turned}
end :: On -> (Pack, [Card]) -> IO Game end :: Ord player => On player -> (Pack, [Card]) -> IO (Game player)
end on@(On_ {month, trick, playing, players}) (river, newCaptured) = do end on@(On_ {month, trick, playing, players}) (river, newCaptured) = do
let updatedGame = setPlayer (on {river, trick = []}) updatedPlayer let updatedGame = setPlayer (on {river, trick = []}) updatedPlayer
if null scored if null scored
@ -37,13 +36,13 @@ end on@(On_ {month, trick, playing, players}) (river, newCaptured) = do
else stop $ updatedGame {step = Scored, winning = playing} else stop $ updatedGame {step = Scored, winning = playing}
where where
newTrick = newCaptured ++ trick newTrick = newCaptured ++ trick
player = players ! playing player = Player.get playing players
(scored, newMeld) = runReader (newTrick `meldInto` (meld player)) month (scored, newMeld) = runReader (newTrick `meldInto` (meld player)) month
updatedPlayer = player {meld = newMeld, yakus = scored `mappend` (yakus player)} updatedPlayer = player {meld = newMeld, yakus = scored `mappend` (yakus player)}
next :: On -> IO Game next :: Ord player => On player -> IO (Game player)
next on@(On_ {players, playing}) = next on@(On_ {players, playing}) =
let newPlaying = Player.next playing in let newPlaying = Player.next players playing in
if hand (players ! newPlaying) == empty if hand (Player.get newPlaying players) == empty
then Round.next $ on then Round.next $ on
else stop $ on {playing = newPlaying, step = ToPlay} else stop $ on {playing = newPlaying, step = ToPlay}

View File

@ -2,51 +2,67 @@
module Hanafuda.Player where module Hanafuda.Player where
import Hanafuda (Card, Pack, contains, packOfCards, remove) import Hanafuda (Card, Pack, contains, packOfCards, remove)
import Data.Map (Map, fromList) import Data.Map ((!), Map, adjust, elemAt, empty, findMin, fromList, insert, keys, singleton, size)
import qualified Data.Map as Map (filter)
import System.Random (Random(..)) import System.Random (Random(..))
data Seat = data Player key yakus = Player {
Player1
| Player2
deriving (Eq, Ord, Show, Enum)
instance Random Seat where
randomR (lo, hi) g =
let (n, g') = randomR (fromEnum lo, fromEnum hi) g in
(toEnum n, g')
random = randomR (Player1, Player2)
next :: Seat -> Seat
next Player1 = Player2
next _ = Player1
data Player a = Player {
hand :: Pack hand :: Pack
, meld :: Pack , meld :: Pack
, yakus :: a , nextPlayer :: key
, yakus :: yakus
} deriving (Show) } deriving (Show)
type Players a = Map Seat (Player a) newtype Players key yakus = Players (Map key (Player key yakus)) deriving (Show)
deal :: [a] -> Map Seat a new :: Monoid yakus => key -> Player key yakus
deal = fromList . zip [Player1, Player2] new nextPlayer = Player {
hand = packOfCards []
new :: Monoid a => [Card] -> Player a
new cards = Player {
hand = packOfCards cards
, meld = packOfCards [] , meld = packOfCards []
, nextPlayer
, yakus = mempty , yakus = mempty
} }
plays :: Player a -> Card -> Either String (Player a) players :: (Ord key, Monoid yakus) => [key] -> Players key yakus
players [] = Players empty
players [player] = Players $ singleton player $ new player
players (alice:others@(bob:_)) =
let Players playersByKey = players others in
let (before, _) = findMin $ Map.filter ((== bob) . nextPlayer) playersByKey in
Players $ insert alice (new bob) $ adjust (setNextPlayer alice) before playersByKey
where
setNextPlayer nextPlayer player = player {nextPlayer}
next :: Ord key => Players key yakus -> key -> key
next (Players playersByKey) = nextPlayer . (playersByKey !)
random :: Players key yakus -> IO key
random (Players playersByKey) =
fst . ($ playersByKey) . elemAt <$> randomRIO (0, size playersByKey - 1)
get :: Ord key => key -> Players key yakus -> Player key yakus
get key (Players playersByKey) = playersByKey ! key
set :: Ord key => key -> Player key yakus -> Players key yakus -> Players key yakus
set key player (Players playersByKey) = Players $ insert key player playersByKey
deal :: Ord key => Players key yakus -> [[Card]] -> Players key yakus
deal (Players playersByKey) hands =
Players $ snd $ foldl dealTo (fst $ findMin playersByKey, playersByKey) hands
where
setHand cards player = player {hand = packOfCards cards}
dealTo (key, m) hand = (nextPlayer $ m ! key, adjust (setHand hand) key m)
plays :: Player key yakus -> Card -> Either String (Player key yakus)
plays player@(Player {hand}) card = plays player@(Player {hand}) card =
if hand `contains` card if hand `contains` card
then Right $ player {hand = remove hand card} then Right $ player {hand = remove hand card}
else Left "You don't have this card" else Left "You don't have this card"
type Points = Int type Points = Int
type Scores key = Map key Points
score :: (a -> Points) -> Player a -> Int score :: (yakus -> Points) -> Player key yakus -> Points
score rater = rater . yakus score rater = rater . yakus
type Scores = Map Seat Points scores :: Ord key => Players key yakus -> [Points] -> Scores key
scores (Players playersByKey) = fromList . zip (keys playersByKey)