lib/src/Hanafuda/KoiKoi/Round.hs

44 lines
1.3 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, next, new, score)
import Data.Map ((!), insert)
import Control.Monad.State (replicateM, runState, state)
deal :: On -> IO On
deal on = do
([hand1, hand2, river], stock) <- fmap (runState (replicateM 3 take8)) $ shuffle cards
return on {
players = fmap Player.new $ Player.deal [hand1, hand2]
, stock
, river = packOfCards river
}
where
take8 = state $ splitAt 8
next :: On -> IO Game
next on@(On_ {mode, scores, month, players, oyake, winning}) =
case mode of
FirstAt n | n <= newScore -> end scored
FirstAt n -> continue
WholeYear | month == Paulownia -> end scored
WholeYear -> continue
where
playing = Player.next oyake
newScore = (scores ! winning) + Player.score sumYakus (players ! winning)
scored = on {scores = insert winning newScore scores}
continue =
deal (scored {
month = succ month
, playing
, winning = playing
, oyake = playing
, step = ToPlay
}) >>= stop