create BuilderState for in-play buildings and Builder's Hall
This commit is contained in:
parent
a3b6810e0e
commit
fdca9de867
17
src/Test.hs
17
src/Test.hs
|
|
@ -53,35 +53,35 @@ b1 = Building { _buildingCost = 6
|
||||||
, _buildingTitle = "Monastary"
|
, _buildingTitle = "Monastary"
|
||||||
, _buildingAction = Group [TakeResource [Cleric], TakeResource [Cleric]]
|
, _buildingAction = Group [TakeResource [Cleric], TakeResource [Cleric]]
|
||||||
, _buildingOwnerAction = TakeResource [Cleric]
|
, _buildingOwnerAction = TakeResource [Cleric]
|
||||||
, _buildingAccumulation = NoAccumulation
|
, _buildingAccumType = NoAccumulation
|
||||||
}
|
}
|
||||||
|
|
||||||
b2 = Building { _buildingCost = 4
|
b2 = Building { _buildingCost = 4
|
||||||
, _buildingTitle = "Training Hall"
|
, _buildingTitle = "Training Hall"
|
||||||
, _buildingAction = Group [TakeResource [Fighter], TakeResource [Fighter]]
|
, _buildingAction = Group [TakeResource [Fighter], TakeResource [Fighter]]
|
||||||
, _buildingOwnerAction = TakeResource [Fighter]
|
, _buildingOwnerAction = TakeResource [Fighter]
|
||||||
, _buildingAccumulation = NoAccumulation
|
, _buildingAccumType = NoAccumulation
|
||||||
}
|
}
|
||||||
|
|
||||||
b3 = Building { _buildingCost = 4
|
b3 = Building { _buildingCost = 4
|
||||||
, _buildingTitle = "Prison Yard"
|
, _buildingTitle = "Prison Yard"
|
||||||
, _buildingAction = Group [TakeResource [Rogue], TakeResource [Rogue]]
|
, _buildingAction = Group [TakeResource [Rogue], TakeResource [Rogue]]
|
||||||
, _buildingOwnerAction = TakeResource [Rogue]
|
, _buildingOwnerAction = TakeResource [Rogue]
|
||||||
, _buildingAccumulation = NoAccumulation
|
, _buildingAccumType = NoAccumulation
|
||||||
}
|
}
|
||||||
|
|
||||||
b4 = Building { _buildingCost = 6
|
b4 = Building { _buildingCost = 6
|
||||||
, _buildingTitle = "Wizard School"
|
, _buildingTitle = "Wizard School"
|
||||||
, _buildingAction = Group [TakeResource [Wizard], TakeResource [Wizard]]
|
, _buildingAction = Group [TakeResource [Wizard], TakeResource [Wizard]]
|
||||||
, _buildingOwnerAction = TakeResource [Wizard]
|
, _buildingOwnerAction = TakeResource [Wizard]
|
||||||
, _buildingAccumulation = NoAccumulation
|
, _buildingAccumType = NoAccumulation
|
||||||
}
|
}
|
||||||
|
|
||||||
b5 = Building { _buildingCost = 4
|
b5 = Building { _buildingCost = 4
|
||||||
, _buildingTitle = "Gold Mine"
|
, _buildingTitle = "Gold Mine"
|
||||||
, _buildingAction = Group $ replicate 4 $ TakeResource [Gold]
|
, _buildingAction = Group $ replicate 4 $ TakeResource [Gold]
|
||||||
, _buildingOwnerAction = Group $ replicate 2 $ TakeResource [Gold]
|
, _buildingOwnerAction = Group $ replicate 2 $ TakeResource [Gold]
|
||||||
, _buildingAccumulation = NoAccumulation
|
, _buildingAccumType = NoAccumulation
|
||||||
}
|
}
|
||||||
|
|
||||||
printWaterdeep :: WaterdeepState -> IO ()
|
printWaterdeep :: WaterdeepState -> IO ()
|
||||||
|
|
@ -99,8 +99,11 @@ printWaterdeep w = do
|
||||||
putStrLn (" " ++ (q ^. questTitle))
|
putStrLn (" " ++ (q ^. questTitle))
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
putStrLn "Builder's Hall:"
|
putStrLn "Builder's Hall:"
|
||||||
forM_ (w ^. gameBuildersHall) $ \(b,agents,pts) -> do
|
forM_ (w ^. gameBuildersHall) $ \b -> do
|
||||||
printf " %s (%d gold -> %d points)\n" (b ^. buildingTitle) (b ^. buildingCost) pts
|
printf " %s (%d gold -> %d points)\n"
|
||||||
|
(b ^. building . buildingTitle)
|
||||||
|
(b ^. building . buildingCost)
|
||||||
|
(b ^. buildingAccumulation)
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
forM_ ps $ \p -> do
|
forM_ ps $ \p -> do
|
||||||
putStrLn ((p ^. playerName) ++ "'s State:")
|
putStrLn ((p ^. playerName) ++ "'s State:")
|
||||||
|
|
|
||||||
|
|
@ -51,7 +51,7 @@ newGame players quests intrigues buildings
|
||||||
, _gameIntrigueDiscard = []
|
, _gameIntrigueDiscard = []
|
||||||
, _gameBuildingDeck = buildings'
|
, _gameBuildingDeck = buildings'
|
||||||
, _gameBuildingDiscard = []
|
, _gameBuildingDiscard = []
|
||||||
, _gameBasicBuildings = map (\b -> (b, [])) basicBuildings
|
, _gameBasicBuildings = map (newBuildingState noPlayerID) basicBuildings
|
||||||
, _gameBuildersHall = []
|
, _gameBuildersHall = []
|
||||||
, _gameAdvancedBuildings = []
|
, _gameAdvancedBuildings = []
|
||||||
, _gameWaterdeepHarbor = ([], [], [])
|
, _gameWaterdeepHarbor = ([], [], [])
|
||||||
|
|
@ -92,6 +92,15 @@ newPlayerState i name faction lord =
|
||||||
, _playerHasAmbassador = False
|
, _playerHasAmbassador = False
|
||||||
}
|
}
|
||||||
|
|
||||||
|
newBuildingState :: PlayerID -> Building -> BuildingState
|
||||||
|
newBuildingState p b =
|
||||||
|
BuildingState
|
||||||
|
{ _building = b
|
||||||
|
, _buildingOwner = p
|
||||||
|
, _buildingAgents = []
|
||||||
|
, _buildingAccumulation = 0
|
||||||
|
}
|
||||||
|
|
||||||
basicBuildings :: [Building]
|
basicBuildings :: [Building]
|
||||||
basicBuildings = []
|
basicBuildings = []
|
||||||
|
|
||||||
|
|
@ -108,10 +117,10 @@ beginRound :: Int -> Waterdeep ()
|
||||||
beginRound round = do
|
beginRound round = do
|
||||||
gameCurrentRound .= round
|
gameCurrentRound .= round
|
||||||
gameCurrentPlayer <~ use gameFirstPlayer
|
gameCurrentPlayer <~ use gameFirstPlayer
|
||||||
gameBasicBuildings . traverse . _2 .= []
|
gameBasicBuildings . traverse . buildingAgents .= []
|
||||||
gameAdvancedBuildings . traverse . _2 .= []
|
gameAdvancedBuildings . traverse . buildingAgents .= []
|
||||||
gameBuildersHall . traverse . _2 .= []
|
gameBuildersHall . traverse . buildingAgents .= []
|
||||||
gameBuildersHall . traverse . _3 += 1
|
gameBuildersHall . traverse . buildingAccumulation += 1
|
||||||
players <- IM.size <$> use gamePlayers
|
players <- IM.size <$> use gamePlayers
|
||||||
forM_ [1..players] $ \p -> do
|
forM_ [1..players] $ \p -> do
|
||||||
qs <- gamePlayer p . playerUsedPlotQuests <<.= []
|
qs <- gamePlayer p . playerUsedPlotQuests <<.= []
|
||||||
|
|
@ -214,5 +223,5 @@ restockBuildersHall = do
|
||||||
case mb of
|
case mb of
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
Just b -> do
|
Just b -> do
|
||||||
gameBuildersHall %= (++ [(b, [], 0)])
|
gameBuildersHall %= (++ [newBuildingState noPlayerID b])
|
||||||
restockBuildersHall
|
restockBuildersHall
|
||||||
|
|
|
||||||
|
|
@ -9,6 +9,7 @@ module Waterdeep.Types
|
||||||
, Quest(..)
|
, Quest(..)
|
||||||
, IntrigueCard(..)
|
, IntrigueCard(..)
|
||||||
, PlayerState(..)
|
, PlayerState(..)
|
||||||
|
, BuildingState(..)
|
||||||
, WaterdeepState(..)
|
, WaterdeepState(..)
|
||||||
, Resource(..)
|
, Resource(..)
|
||||||
, QuestType(..)
|
, QuestType(..)
|
||||||
|
|
@ -28,7 +29,7 @@ module Waterdeep.Types
|
||||||
, buildingTitle
|
, buildingTitle
|
||||||
, buildingAction
|
, buildingAction
|
||||||
, buildingOwnerAction
|
, buildingOwnerAction
|
||||||
, buildingAccumulation
|
, buildingAccumType
|
||||||
, questType
|
, questType
|
||||||
, questTitle
|
, questTitle
|
||||||
, questQuote
|
, questQuote
|
||||||
|
|
@ -52,6 +53,10 @@ module Waterdeep.Types
|
||||||
, playerAgentsInPool
|
, playerAgentsInPool
|
||||||
, playerHasLieutenant
|
, playerHasLieutenant
|
||||||
, playerHasAmbassador
|
, playerHasAmbassador
|
||||||
|
, building
|
||||||
|
, buildingAgents
|
||||||
|
, buildingOwner
|
||||||
|
, buildingAccumulation
|
||||||
, gamePlayers
|
, gamePlayers
|
||||||
, gameFirstPlayer
|
, gameFirstPlayer
|
||||||
, gameCurrentRound
|
, gameCurrentRound
|
||||||
|
|
@ -70,6 +75,7 @@ module Waterdeep.Types
|
||||||
, gameWaterdeepHarbor
|
, gameWaterdeepHarbor
|
||||||
, gameStdGen
|
, gameStdGen
|
||||||
, gamePlayer
|
, gamePlayer
|
||||||
|
, noPlayerID
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
|
|
@ -98,7 +104,7 @@ data Building =
|
||||||
, _buildingTitle :: String
|
, _buildingTitle :: String
|
||||||
, _buildingAction :: GameAction
|
, _buildingAction :: GameAction
|
||||||
, _buildingOwnerAction :: GameAction
|
, _buildingOwnerAction :: GameAction
|
||||||
, _buildingAccumulation :: AccumulationType
|
, _buildingAccumType :: AccumulationType
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
data Quest =
|
data Quest =
|
||||||
|
|
@ -136,6 +142,14 @@ data PlayerState =
|
||||||
, _playerHasAmbassador :: Bool
|
, _playerHasAmbassador :: Bool
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
|
data BuildingState =
|
||||||
|
BuildingState
|
||||||
|
{ _building :: Building
|
||||||
|
, _buildingAgents :: [PlayerID]
|
||||||
|
, _buildingOwner :: PlayerID
|
||||||
|
, _buildingAccumulation :: Int
|
||||||
|
} deriving (Show)
|
||||||
|
|
||||||
data WaterdeepState =
|
data WaterdeepState =
|
||||||
WaterdeepState
|
WaterdeepState
|
||||||
{ _gamePlayers :: IntMap PlayerState
|
{ _gamePlayers :: IntMap PlayerState
|
||||||
|
|
@ -150,9 +164,9 @@ data WaterdeepState =
|
||||||
, _gameIntrigueDiscard :: [IntrigueCard]
|
, _gameIntrigueDiscard :: [IntrigueCard]
|
||||||
, _gameBuildingDeck :: [Building]
|
, _gameBuildingDeck :: [Building]
|
||||||
, _gameBuildingDiscard :: [Building]
|
, _gameBuildingDiscard :: [Building]
|
||||||
, _gameBasicBuildings :: [(Building, [PlayerID])]
|
, _gameBasicBuildings :: [BuildingState]
|
||||||
, _gameBuildersHall :: [(Building, [PlayerID], Int)]
|
, _gameBuildersHall :: [BuildingState]
|
||||||
, _gameAdvancedBuildings :: [(Building, [PlayerID], Int, Int)]
|
, _gameAdvancedBuildings :: [BuildingState]
|
||||||
, _gameWaterdeepHarbor :: ([PlayerID], [PlayerID], [PlayerID])
|
, _gameWaterdeepHarbor :: ([PlayerID], [PlayerID], [PlayerID])
|
||||||
, _gameStdGen :: StdGen
|
, _gameStdGen :: StdGen
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
@ -237,12 +251,16 @@ makeLenses ''Building
|
||||||
makeLenses ''Quest
|
makeLenses ''Quest
|
||||||
makeLenses ''IntrigueCard
|
makeLenses ''IntrigueCard
|
||||||
makeLenses ''PlayerState
|
makeLenses ''PlayerState
|
||||||
|
makeLenses ''BuildingState
|
||||||
makeLenses ''WaterdeepState
|
makeLenses ''WaterdeepState
|
||||||
|
|
||||||
gamePlayer :: PlayerID -> Lens' WaterdeepState PlayerState
|
gamePlayer :: PlayerID -> Lens' WaterdeepState PlayerState
|
||||||
gamePlayer n = lens (\w -> w ^. gamePlayers.singular (ix n))
|
gamePlayer n = lens (\w -> w ^. gamePlayers.singular (ix n))
|
||||||
(\w p -> w & gamePlayers.singular (ix n) .~ p)
|
(\w p -> w & gamePlayers.singular (ix n) .~ p)
|
||||||
|
|
||||||
|
noPlayerID :: PlayerID
|
||||||
|
noPlayerID = 0
|
||||||
|
|
||||||
instance Eq Faction where
|
instance Eq Faction where
|
||||||
a == b = a^.factionColor == b^.factionColor
|
a == b = a^.factionColor == b^.factionColor
|
||||||
|
|
||||||
|
|
|
||||||
Loading…
Reference in New Issue