summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorFrederick Yin <fkfd@fkfd.me>2023-01-11 15:44:42 +0800
committerFrederick Yin <fkfd@fkfd.me>2023-01-11 15:44:42 +0800
commitc01a05c12636382db64799f3e6184c0b0f269bc6 (patch)
tree128d94fd5bbb51d4028ce3fbafa072010480101e
parentb26b53b25655eee6254ebae446d606b3943d17af (diff)
Print penalties at end of round
-rw-r--r--Game.hs20
-rw-r--r--Main.hs4
-rw-r--r--Player.hs12
3 files changed, 29 insertions, 7 deletions
diff --git a/Game.hs b/Game.hs
index 99b3486..08016c9 100644
--- a/Game.hs
+++ b/Game.hs
@@ -1,9 +1,9 @@
module Game where
import Data.Char (isDigit)
-import Control.Monad (when)
+import Control.Monad (mapM_)
import System.Random (RandomGen, newStdGen)
-import Player (Player, shed, draw)
+import Player (Player(..), shed, draw)
import qualified Player as P
import Card (Card(..))
import qualified Card as C
@@ -44,7 +44,7 @@ beginTurn auto game@(Game plyrs pidx att dir prev stock disc) = do
putStrLn $ replicate 80 '-'
putStrLn $ P.name player ++ "'s turn (input 0 to skip turn and draw card)"
- putStrLn $ P.showCards player prev att
+ -- putStrLn $ P.showCards player prev att
putStrLn $ "Stock: " ++ (show $ length stock)
++ ", Discard: " ++ (show $ length disc)
putStrLn $ "Current attack: " ++ show att
@@ -58,7 +58,7 @@ beginTurn auto game@(Game plyrs pidx att dir prev stock disc) = do
Just card -> shedAndContinue card game
if playerIdx game' == pidx -- shedAndContinue does this when player wins
- then return game'
+ then endRound game'
else beginTurn auto game'
-- | Game state after player draws card(s) and skips turn.
@@ -138,3 +138,15 @@ automate game@(Game plyrs pidx att _ prev _ _) =
then Nothing
else Just (head validCards)
where validCards = filter (C.isValid prev att) $ P.cards (plyrs !! pidx)
+
+-- | Keep penalties and reset game for next round.
+endRound :: Game -> IO Game
+endRound game@(Game plyrs pidx _ _ _ stock disc) = do
+ putStrLn $ (P.name $ plyrs !! pidx) ++ " wins this round!"
+ let plyrs' = P.calcPenalties plyrs
+ putStrLn "Penalties:"
+ putStrLn $ P.showPenalties plyrs'
+ return $ Game plyrs' pidx 1 1 (head stock) (tail stock) disc
+
+wait :: a -> IO a
+wait x = getLine >> return x
diff --git a/Main.hs b/Main.hs
index 70c9df7..c21cdab 100644
--- a/Main.hs
+++ b/Main.hs
@@ -34,5 +34,5 @@ main = do
, discardPile = discard
}
- beginRounds 1 False $ dealCards 6 game
- print ()
+ beginRounds 3 True $ dealCards 6 game
+ return ()
diff --git a/Player.hs b/Player.hs
index 5aad025..ec4d180 100644
--- a/Player.hs
+++ b/Player.hs
@@ -6,7 +6,7 @@ import qualified Card as C
import qualified Color
data Player = Player { name :: String
- , penalty :: Integer
+ , penalty :: Int
, cards :: [Card]
}
@@ -35,3 +35,13 @@ showCards (Player _ _ cs) prev att =
else join n c
else Color.red $ join n c
join n c = (show n) ++ ". " ++ (C.showCard c)
+
+-- | Update penalty for each player after a round.
+calcPenalties :: [Player] -> [Player]
+calcPenalties plyrs = map penalize plyrs
+ where penalize (Player n p c) = Player n (p + length c) c
+
+-- | Pretty print penalties.
+showPenalties :: [Player] -> String
+showPenalties = unlines . map showPenalty
+ where showPenalty (Player n p _) = n ++ ":\t" ++ show p