lib/src/Hanafuda/KoiKoi/Round.hs

47 lines
1.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE NamedFieldPuns #-}
module Hanafuda.KoiKoi.Round (
deal
, next
) where
import Hanafuda (Flower(Paulownia), cards, shuffle, packOfCards)
import Hanafuda.KoiKoi.Yaku (sumYakus)
import Hanafuda.KoiKoi.Game (Game(..), Mode(..), Step(..), end)
import qualified Hanafuda.Player as Player (deal, get, score, yakus)
import Data.Map ((!), insert)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.State (runState, state)
deal :: MonadIO m => Game -> m Game
2019-08-12 23:02:17 +02:00
deal game@(Game {players}) = do
((hand1, hand2, river), deck) <- runState getTriple <$> shuffle cards
2019-08-12 23:02:17 +02:00
return game {
players = Player.deal players [hand1, hand2]
, deck
, river = packOfCards river
}
where
take8 = state $ splitAt 8
getTriple = (,,) <$> take8 <*> take8 <*> take8
next :: MonadIO m => Game -> m Game
next game@(Game {mode, scores, month, players, nextPlayer, oyake, winning, rounds}) =
case mode of
FirstAt n | n <= newScore -> end scored
2018-03-19 12:28:15 +01:00
FirstAt _ -> continue
WholeYear | month == Paulownia -> end scored
WholeYear -> continue
where
playing = nextPlayer ! oyake
2019-08-12 23:02:17 +02:00
winner = Player.get winning players
newScore = (scores ! winning) + Player.score sumYakus winner
scored = game {scores = insert winning newScore scores, rounds = (winning, Player.yakus winner): rounds}
continue =
deal (scored {
month = succ month
, playing
, winning = playing
, oyake = playing
, step = ToPlay
2019-08-12 23:02:17 +02:00
})