use Data.MultiSet to represent resources in place of Data.Map
This commit is contained in:
parent
e7802f17bd
commit
0f035e74cc
|
|
@ -23,8 +23,9 @@ import Waterdeep.Logic
|
|||
import Waterdeep.Types
|
||||
import Waterdeep.Util
|
||||
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.MultiSet as MS
|
||||
|
||||
data DisplayState =
|
||||
DisplayState
|
||||
|
|
@ -119,8 +120,8 @@ i2 = IntrigueCard { _intrigueTitle = "Call for Adventurers"
|
|||
clearScreen :: IO ()
|
||||
clearScreen = putStr "\o033[H\o033[2J" >> hFlush stdout
|
||||
|
||||
showTavern :: M.Map Resource Int -> String
|
||||
showTavern = intercalate ", " . map showResource . M.toAscList
|
||||
showTavern :: MS.MultiSet Resource -> String
|
||||
showTavern = intercalate ", " . map showResource . MS.toAscOccurList
|
||||
where showResource (r, n) = show n ++ " " ++ show r
|
||||
|
||||
printWaterdeep :: WaterdeepState -> IO ()
|
||||
|
|
|
|||
|
|
@ -57,8 +57,9 @@ import Text.Printf
|
|||
import Waterdeep.Types
|
||||
import Waterdeep.Util
|
||||
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.MultiSet as MS
|
||||
|
||||
noAction :: GameAction
|
||||
noAction = return ()
|
||||
|
|
@ -73,7 +74,7 @@ takeResources :: Int -> [Resource] -> GameAction
|
|||
takeResources n rs = do
|
||||
received <- map (head &&& length) . group . sort <$$> replicateM n $ do
|
||||
r <- solicitChoice "Take one item:" $ map (show &&& id) rs
|
||||
activePlayerState . playerTavern %= M.insertWith' (+) r 1
|
||||
activePlayerState . playerTavern <>= MS.singleton r
|
||||
return r
|
||||
let items = joinStrings $ map (\(r,n) -> show n ++ " " ++ show r) received
|
||||
name <- use $ activePlayerName
|
||||
|
|
@ -82,11 +83,9 @@ takeResources n rs = do
|
|||
returnResources :: Int -> [Resource] -> GameAction
|
||||
returnResources n rs = do
|
||||
returned <- replicateM n $ do
|
||||
tavern <- use $ activePlayerState . playerTavern
|
||||
let rs' = filter ((>= 1) . maybe 0 id . flip M.lookup tavern) rs
|
||||
r <- solicitChoice "Return one item:" $ map (show &&& id) rs'
|
||||
let removeOne x = if x > 1 then Just (x-1) else Nothing
|
||||
activePlayerState . playerTavern %= M.update removeOne r
|
||||
r <- solicitChoice "Return one item:" $ map (show &&& id) rs
|
||||
guard . (r `MS.member`) =<< use (activePlayerState . playerTavern)
|
||||
activePlayerState . playerTavern %= (`MS.difference` MS.singleton r)
|
||||
return r
|
||||
let groups = map (head &&& length) $ group returned
|
||||
let items = joinStrings $ map (\(r,n) -> show n ++ " " ++ show r) groups
|
||||
|
|
|
|||
|
|
@ -25,8 +25,9 @@ import Waterdeep.Actions
|
|||
import Waterdeep.Types
|
||||
import Waterdeep.Util
|
||||
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.MultiSet as MS
|
||||
|
||||
newGame :: [(String,Faction,Lord)]
|
||||
-> [Quest]
|
||||
|
|
@ -139,7 +140,7 @@ scoreFinalPoints :: Waterdeep ()
|
|||
scoreFinalPoints = do
|
||||
np <- use gameNumberOfPlayers
|
||||
forM_ [1..np] $ \p -> withActivePlayer p $ do
|
||||
rs <- M.toAscList <$> use (activePlayerState . playerTavern)
|
||||
rs <- MS.toAscOccurList <$> use (activePlayerState . playerTavern)
|
||||
name <- use activePlayerName
|
||||
forM_ rs $ \(r, n) -> do
|
||||
let pts = case r of { Gold -> n `div` 2; _ -> n; }
|
||||
|
|
@ -173,7 +174,7 @@ determineWinners = do
|
|||
let winners2 = filter ((== bestGold) . playerGold) winners1
|
||||
return (winners2 ^.. each . playerNumber)
|
||||
where
|
||||
playerGold = maybe 0 id . M.lookup Gold . view playerTavern
|
||||
playerGold = MS.occur Gold . view playerTavern
|
||||
|
||||
initialAgents :: Int -> Int -> Int
|
||||
initialAgents players round =
|
||||
|
|
|
|||
|
|
@ -117,6 +117,7 @@ import System.Random (StdGen)
|
|||
|
||||
import qualified Data.IntMap as IM
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.MultiSet as MS
|
||||
import qualified System.Random as R
|
||||
|
||||
type PlayerID = Int
|
||||
|
|
@ -169,7 +170,7 @@ data PlayerState =
|
|||
, _playerFaction :: Faction
|
||||
, _playerLord :: Lord
|
||||
, _playerScore :: Int
|
||||
, _playerTavern :: Map Resource Int
|
||||
, _playerTavern :: MS.MultiSet Resource
|
||||
, _playerIncompleteQuests :: [Quest]
|
||||
, _playerCompletedQuests :: [Quest]
|
||||
, _playerActivePlotQuests :: [Quest]
|
||||
|
|
@ -340,7 +341,7 @@ newPlayerState i (name, faction, lord) =
|
|||
, _playerFaction = faction
|
||||
, _playerLord = lord
|
||||
, _playerScore = 0
|
||||
, _playerTavern = M.empty
|
||||
, _playerTavern = mempty
|
||||
, _playerIncompleteQuests = []
|
||||
, _playerCompletedQuests = []
|
||||
, _playerActivePlotQuests = []
|
||||
|
|
|
|||
Loading…
Reference in New Issue