lib/src/Hanafuda/KoiKoi/Round.hs

46 lines
1.5 KiB
Haskell

{-# 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(..), On(..), Step(..), end, stop)
import qualified Hanafuda.Player as Player (deal, get, next, score)
import Data.Map ((!), insert)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.State (runState, state)
deal :: (MonadIO m, Ord player) => On player -> m (On player)
deal on@(On_ {players}) = do
((hand1, hand2, river), deck) <- runState getTriple <$> shuffle cards
return on {
players = Player.deal players [hand1, hand2]
, deck
, river = packOfCards river
}
where
take8 = state $ splitAt 8
getTriple = (,,) <$> take8 <*> take8 <*> take8
next :: (MonadIO m, Ord player) => On player -> m (Game player)
next on@(On_ {mode, scores, month, players, oyake, winning}) =
case mode of
FirstAt n | n <= newScore -> end scored
FirstAt _ -> continue
WholeYear | month == Paulownia -> end scored
WholeYear -> continue
where
playing = Player.next players oyake
newScore = (scores ! winning) + Player.score sumYakus (Player.get winning players)
scored = on {scores = insert winning newScore scores}
continue =
deal (scored {
month = succ month
, playing
, winning = playing
, oyake = playing
, step = ToPlay
}) >>= stop