renamed GameState fields to prevent name collisions

This commit is contained in:
Jonathan Lamothe 2019-11-04 01:48:47 -05:00
parent 3f38160abd
commit 43f3d9eb08
6 changed files with 69 additions and 69 deletions

View File

@ -203,7 +203,7 @@ resetCreateGoalieState = progMode.createGoalieStateL
-- | Attempts to finish game goalie entry -- | Attempts to finish game goalie entry
finishGameGoalieEntry :: ProgState -> ProgState finishGameGoalieEntry :: ProgState -> ProgState
finishGameGoalieEntry s = s & progMode.gameStateL.goaliesRecorded finishGameGoalieEntry s = s & progMode.gameStateL.gameGoaliesRecorded
.~ not (null $ s^.progMode.gameStateL.gameGoalieStats) .~ not (null $ s^.progMode.gameStateL.gameGoalieStats)
-- | Awards the goal and assists to the players -- | Awards the goal and assists to the players
@ -271,7 +271,7 @@ assignPMins
-> ProgState -> ProgState
-> ProgState -> ProgState
assignPMins mins s = fromMaybe s $ do assignPMins mins s = fromMaybe s $ do
n <- s^.progMode.gameStateL.selectedPlayer n <- s^.progMode.gameStateL.gameSelectedPlayer
Just $ s Just $ s
& database.dbPlayers %~ modifyNth n & database.dbPlayers %~ modifyNth n
(((pYtd.psPMin) +~ mins) . ((pLifetime.psPMin) +~ mins)) (((pYtd.psPMin) +~ mins) . ((pLifetime.psPMin) +~ mins))
@ -279,7 +279,7 @@ assignPMins mins s = fromMaybe s $ do
%~ ( gamePlayerStats %~ updateMap n newPlayerStats %~ ( gamePlayerStats %~ updateMap n newPlayerStats
(psPMin +~ mins) (psPMin +~ mins)
) )
. (selectedPlayer .~ Nothing) . (gameSelectedPlayer .~ Nothing)
-- | Records the goalie's game stats -- | Records the goalie's game stats
recordGoalieStats :: ProgState -> ProgState recordGoalieStats :: ProgState -> ProgState
@ -287,8 +287,8 @@ recordGoalieStats s = fromMaybe s $ do
let gs = s^.progMode.gameStateL let gs = s^.progMode.gameStateL
gid <- gs^.gameSelectedGoalie gid <- gs^.gameSelectedGoalie
goalie <- nth gid $ s^.database.dbGoalies goalie <- nth gid $ s^.database.dbGoalies
mins <- gs^.goalieMinsPlayed mins <- gs^.gameGoalieMinsPlayed
goals <- gs^.goalsAllowed goals <- gs^.gameGoalsAllowed
let let
gameStats = M.findWithDefault newGoalieStats gid $ gs^.gameGoalieStats gameStats = M.findWithDefault newGoalieStats gid $ gs^.gameGoalieStats
@ -304,9 +304,9 @@ recordGoalieStats s = fromMaybe s $ do
Just $ s Just $ s
& progMode.gameStateL & progMode.gameStateL
%~ (gameGoalieStats %~ updateMap gid newGoalieStats bumpStats) %~ (gameGoalieStats %~ updateMap gid newGoalieStats bumpStats)
. (gameSelectedGoalie .~ Nothing) . (gameSelectedGoalie .~ Nothing)
. (goalieMinsPlayed .~ Nothing) . (gameGoalieMinsPlayed .~ Nothing)
. (goalsAllowed .~ Nothing) . (gameGoalsAllowed .~ Nothing)
& database.dbGoalies & database.dbGoalies
%~ modifyNth gid (\goalie -> goalie %~ modifyNth gid (\goalie -> goalie
& gYtd %~ bumpStats & gYtd %~ bumpStats

View File

@ -58,9 +58,9 @@ dispatch s = case s^.progMode of
| null $ gs^.overtimeFlag -> overtimeFlagC | null $ gs^.overtimeFlag -> overtimeFlagC
| not $ gs^.dataVerified -> verifyDataC | not $ gs^.dataVerified -> verifyDataC
| fromJust (unaccountedPoints gs) -> goalInput gs | fromJust (unaccountedPoints gs) -> goalInput gs
| isJust $ gs^.selectedPlayer -> getPMinsC | isJust $ gs^.gameSelectedPlayer -> getPMinsC
| not $ gs^.pMinsRecorded -> pMinPlayerC | not $ gs^.gamePMinsRecorded -> pMinPlayerC
| not $ gs^.goaliesRecorded -> goalieInput gs | not $ gs^.gameGoaliesRecorded -> goalieInput gs
| otherwise -> reportC | otherwise -> reportC
CreatePlayer cps CreatePlayer cps
| null $ cps^.cpsNumber -> getPlayerNumC | null $ cps^.cpsNumber -> getPlayerNumC
@ -267,7 +267,7 @@ getPMinsC = Controller
{ drawController = \s -> do { drawController = \s -> do
header s header s
C.drawString $ fromMaybe "" $ do C.drawString $ fromMaybe "" $ do
pid <- s^.progMode.gameStateL.selectedPlayer pid <- s^.progMode.gameStateL.gameSelectedPlayer
player <- nth pid $ s^.database.dbPlayers player <- nth pid $ s^.database.dbPlayers
Just $ playerSummary player ++ "\n" Just $ playerSummary player ++ "\n"
drawPrompt assignPMinsPrompt s drawPrompt assignPMinsPrompt s

View File

@ -33,9 +33,9 @@ import Mtlstats.Util
-- | The dispatcher for handling goalie input -- | The dispatcher for handling goalie input
goalieInput :: GameState -> Controller goalieInput :: GameState -> Controller
goalieInput gs goalieInput gs
| null $ gs^.gameSelectedGoalie = selectGoalieC | null $ gs^.gameSelectedGoalie = selectGoalieC
| null $ gs^.goalieMinsPlayed = minsPlayedC | null $ gs^.gameGoalieMinsPlayed = minsPlayedC
| otherwise = goalsAllowedC | otherwise = goalsAllowedC
selectGoalieC :: Controller selectGoalieC :: Controller
selectGoalieC = Controller selectGoalieC = Controller

View File

@ -316,8 +316,8 @@ pMinPlayerPrompt :: Prompt
pMinPlayerPrompt = selectPlayerPrompt pMinPlayerPrompt = selectPlayerPrompt
"Assign penalty minutes to: " $ "Assign penalty minutes to: " $
\case \case
Nothing -> modify $ progMode.gameStateL.pMinsRecorded .~ True Nothing -> modify $ progMode.gameStateL.gamePMinsRecorded .~ True
Just n -> modify $ progMode.gameStateL.selectedPlayer ?~ n Just n -> modify $ progMode.gameStateL.gameSelectedPlayer ?~ n
-- | Prompts for the number of penalty mintues to assign to the player -- | Prompts for the number of penalty mintues to assign to the player
assignPMinsPrompt :: Prompt assignPMinsPrompt :: Prompt
@ -344,15 +344,15 @@ selectGameGoaliePrompt = selectGoaliePrompt "Which goalie played this game: " $
-- | Prompts for the number of minutes the goalie has played -- | Prompts for the number of minutes the goalie has played
goalieMinsPlayedPrompt :: Prompt goalieMinsPlayedPrompt :: Prompt
goalieMinsPlayedPrompt = numPrompt "Minutes played: " $ goalieMinsPlayedPrompt = numPrompt "Minutes played: " $
modify . (progMode.gameStateL.goalieMinsPlayed ?~) modify . (progMode.gameStateL.gameGoalieMinsPlayed ?~)
-- | Prompts for the number of goals the goalie allowed -- | Prompts for the number of goals the goalie allowed
goalsAllowedPrompt :: Prompt goalsAllowedPrompt :: Prompt
goalsAllowedPrompt = numPrompt "Goals allowed: " $ \n -> do goalsAllowedPrompt = numPrompt "Goals allowed: " $ \n -> do
modify (progMode.gameStateL.goalsAllowed ?~ n) modify (progMode.gameStateL.gameGoalsAllowed ?~ n)
mins <- fromMaybe 0 <$> gets (^.progMode.gameStateL.goalieMinsPlayed) mins <- fromMaybe 0 <$> gets (^.progMode.gameStateL.gameGoalieMinsPlayed)
when (mins >= gameLength) $ when (mins >= gameLength) $
modify $ progMode.gameStateL.goaliesRecorded .~ True modify $ progMode.gameStateL.gameGoaliesRecorded .~ True
modify recordGoalieStats modify recordGoalieStats
playerToEditPrompt :: Prompt playerToEditPrompt :: Prompt

View File

@ -67,13 +67,13 @@ module Mtlstats.Types (
assistsBy, assistsBy,
gamePlayerStats, gamePlayerStats,
confirmGoalDataFlag, confirmGoalDataFlag,
selectedPlayer, gameSelectedPlayer,
pMinsRecorded, gamePMinsRecorded,
gameGoalieStats, gameGoalieStats,
gameSelectedGoalie, gameSelectedGoalie,
goalieMinsPlayed, gameGoalieMinsPlayed,
goalsAllowed, gameGoalsAllowed,
goaliesRecorded, gameGoaliesRecorded,
gameGoalieAssigned, gameGoalieAssigned,
-- ** CreatePlayerState Lenses -- ** CreatePlayerState Lenses
cpsNumber, cpsNumber,
@ -252,30 +252,30 @@ data GameState = GameState
, _goalBy :: Maybe Int , _goalBy :: Maybe Int
-- ^ The index number of the player who scored the most recently -- ^ The index number of the player who scored the most recently
-- entered goal -- entered goal
, _assistsBy :: [Int] , _assistsBy :: [Int]
-- ^ The index numbers of the players who have assisted the most -- ^ The index numbers of the players who have assisted the most
-- recently entered goal -- recently entered goal
, _gamePlayerStats :: M.Map Int PlayerStats , _gamePlayerStats :: M.Map Int PlayerStats
-- ^ The player stats accumulated over the game -- ^ The player stats accumulated over the game
, _confirmGoalDataFlag :: Bool , _confirmGoalDataFlag :: Bool
-- ^ Set when the user confirms the goal data -- ^ Set when the user confirms the goal data
, _selectedPlayer :: Maybe Int , _gameSelectedPlayer :: Maybe Int
-- ^ Index number of the selected 'Player' -- ^ Index number of the selected 'Player'
, _pMinsRecorded :: Bool , _gamePMinsRecorded :: Bool
-- ^ Set when the penalty mintes have been recorded -- ^ Set when the penalty mintes have been recorded
, _gameGoalieStats :: M.Map Int GoalieStats , _gameGoalieStats :: M.Map Int GoalieStats
-- ^ The goalie stats accumulated over the game -- ^ The goalie stats accumulated over the game
, _gameSelectedGoalie :: Maybe Int , _gameSelectedGoalie :: Maybe Int
-- ^ Index number of the selected 'Goalie' -- ^ Index number of the selected 'Goalie'
, _goalieMinsPlayed :: Maybe Int , _gameGoalieMinsPlayed :: Maybe Int
-- ^ The number of minutes the currently selected goalie played in -- ^ The number of minutes the currently selected goalie played in
-- the game -- the game
, _goalsAllowed :: Maybe Int , _gameGoalsAllowed :: Maybe Int
-- ^ The number of goals the currently selected goalie allowed in -- ^ The number of goals the currently selected goalie allowed in
-- the game -- the game
, _goaliesRecorded :: Bool , _gameGoaliesRecorded :: Bool
-- ^ Set when the user confirms that all goalie info has been entered -- ^ Set when the user confirms that all goalie info has been entered
, _gameGoalieAssigned :: Bool , _gameGoalieAssigned :: Bool
-- ^ Set to 'True' when the goalie has been selected who will be -- ^ Set to 'True' when the goalie has been selected who will be
-- given the win/loss/tie -- given the win/loss/tie
} deriving (Eq, Show) } deriving (Eq, Show)
@ -628,28 +628,28 @@ newProgState = ProgState
-- | Constructor for a 'GameState' -- | Constructor for a 'GameState'
newGameState :: GameState newGameState :: GameState
newGameState = GameState newGameState = GameState
{ _gameYear = Nothing { _gameYear = Nothing
, _gameMonth = Nothing , _gameMonth = Nothing
, _gameDay = Nothing , _gameDay = Nothing
, _gameType = Nothing , _gameType = Nothing
, _otherTeam = "" , _otherTeam = ""
, _homeScore = Nothing , _homeScore = Nothing
, _awayScore = Nothing , _awayScore = Nothing
, _overtimeFlag = Nothing , _overtimeFlag = Nothing
, _dataVerified = False , _dataVerified = False
, _pointsAccounted = 0 , _pointsAccounted = 0
, _goalBy = Nothing , _goalBy = Nothing
, _assistsBy = [] , _assistsBy = []
, _gamePlayerStats = M.empty , _gamePlayerStats = M.empty
, _confirmGoalDataFlag = False , _confirmGoalDataFlag = False
, _selectedPlayer = Nothing , _gameSelectedPlayer = Nothing
, _pMinsRecorded = False , _gamePMinsRecorded = False
, _gameGoalieStats = M.empty , _gameGoalieStats = M.empty
, _gameSelectedGoalie = Nothing , _gameSelectedGoalie = Nothing
, _goalieMinsPlayed = Nothing , _gameGoalieMinsPlayed = Nothing
, _goalsAllowed = Nothing , _gameGoalsAllowed = Nothing
, _goaliesRecorded = False , _gameGoaliesRecorded = False
, _gameGoalieAssigned = False , _gameGoalieAssigned = False
} }
-- | Constructor for a 'CreatePlayerState' -- | Constructor for a 'CreatePlayerState'

View File

@ -450,12 +450,12 @@ finishGameGoalieEntrySpec = describe "finishGameGoalieEntry" $ do
context "no goalie data" $ context "no goalie data" $
it "should not set goaliesRecorded" $ let it "should not set goaliesRecorded" $ let
s = progState M.empty s = progState M.empty
in s^.progMode.gameStateL.goaliesRecorded `shouldBe` False in s^.progMode.gameStateL.gameGoaliesRecorded `shouldBe` False
context "goalie data" $ context "goalie data" $
it "should set goaliesRecorded" $ let it "should set goaliesRecorded" $ let
s = progState $ M.fromList [(1, newGoalieStats)] s = progState $ M.fromList [(1, newGoalieStats)]
in s^.progMode.gameStateL.goaliesRecorded `shouldBe` True in s^.progMode.gameStateL.gameGoaliesRecorded `shouldBe` True
recordGoalAssistsSpec :: Spec recordGoalAssistsSpec :: Spec
recordGoalAssistsSpec = describe "recordGoalAssists" $ do recordGoalAssistsSpec = describe "recordGoalAssists" $ do
@ -655,7 +655,7 @@ assignPMinsSpec = describe "assignPMins" $ let
& database.dbPlayers .~ [bob, joe] & database.dbPlayers .~ [bob, joe]
& progMode.gameStateL & progMode.gameStateL
%~ (gamePlayerStats .~ M.fromList [(0, newPlayerStats & psPMin .~ 2)]) %~ (gamePlayerStats .~ M.fromList [(0, newPlayerStats & psPMin .~ 2)])
. (selectedPlayer .~ pid) . (gameSelectedPlayer .~ pid)
in mapM_ in mapM_
(\(pid, bobLt, bobYtd, bobGame, joeLt, joeYtd, joeGame) -> (\(pid, bobLt, bobYtd, bobGame, joeLt, joeYtd, joeGame) ->
@ -687,7 +687,7 @@ assignPMinsSpec = describe "assignPMins" $ let
] ]
it "should set selectedPlayer to Nothing" $ it "should set selectedPlayer to Nothing" $
ps'^.progMode.gameStateL.selectedPlayer `shouldBe` Nothing) ps'^.progMode.gameStateL.gameSelectedPlayer `shouldBe` Nothing)
-- index, bob lt, bob ytd, bob game, joe lt, joe ytd, joe game -- index, bob lt, bob ytd, bob game, joe lt, joe ytd, joe game
[ ( Just 0, 6, 5, 4, 6, 5, 0 ) [ ( Just 0, 6, 5, 4, 6, 5, 0 )
@ -712,10 +712,10 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
& gLifetime .~ goalieStats 40 41 42 & gLifetime .~ goalieStats 40 41 42
gameState n mins goals = newGameState gameState n mins goals = newGameState
& gameGoalieStats .~ M.fromList [(1, goalieStats 1 2 3)] & gameGoalieStats .~ M.fromList [(1, goalieStats 1 2 3)]
& gameSelectedGoalie .~ n & gameSelectedGoalie .~ n
& goalieMinsPlayed .~ mins & gameGoalieMinsPlayed .~ mins
& goalsAllowed .~ goals & gameGoalsAllowed .~ goals
progState n mins goals = newProgState progState n mins goals = newProgState
& database.dbGoalies .~ [joe, bob] & database.dbGoalies .~ [joe, bob]
@ -768,12 +768,12 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
context "minutes played" $ let context "minutes played" $ let
expected = if reset then Nothing else mins expected = if reset then Nothing else mins
in it ("should be " ++ show expected) $ in it ("should be " ++ show expected) $
(s^.progMode.gameStateL.goalieMinsPlayed) `shouldBe` expected (s^.progMode.gameStateL.gameGoalieMinsPlayed) `shouldBe` expected
context "goals allowed" $ let context "goals allowed" $ let
expected = if reset then Nothing else goals expected = if reset then Nothing else goals
in it ("should be " ++ show expected) $ in it ("should be " ++ show expected) $
(s^.progMode.gameStateL.goalsAllowed) `shouldBe` expected) (s^.progMode.gameStateL.gameGoalsAllowed) `shouldBe` expected)
[ ( "updating Joe" [ ( "updating Joe"
, Just 0 , Just 0