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

View File

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

View File

@ -34,7 +34,7 @@ import Mtlstats.Util
goalieInput :: GameState -> Controller
goalieInput gs
| null $ gs^.gameSelectedGoalie = selectGoalieC
| null $ gs^.goalieMinsPlayed = minsPlayedC
| null $ gs^.gameGoalieMinsPlayed = minsPlayedC
| otherwise = goalsAllowedC
selectGoalieC :: Controller

View File

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

View File

@ -67,13 +67,13 @@ module Mtlstats.Types (
assistsBy,
gamePlayerStats,
confirmGoalDataFlag,
selectedPlayer,
pMinsRecorded,
gameSelectedPlayer,
gamePMinsRecorded,
gameGoalieStats,
gameSelectedGoalie,
goalieMinsPlayed,
goalsAllowed,
goaliesRecorded,
gameGoalieMinsPlayed,
gameGoalsAllowed,
gameGoaliesRecorded,
gameGoalieAssigned,
-- ** CreatePlayerState Lenses
cpsNumber,
@ -259,21 +259,21 @@ data GameState = GameState
-- ^ The player stats accumulated over the game
, _confirmGoalDataFlag :: Bool
-- ^ Set when the user confirms the goal data
, _selectedPlayer :: Maybe Int
, _gameSelectedPlayer :: Maybe Int
-- ^ Index number of the selected 'Player'
, _pMinsRecorded :: Bool
, _gamePMinsRecorded :: Bool
-- ^ Set when the penalty mintes have been recorded
, _gameGoalieStats :: M.Map Int GoalieStats
-- ^ The goalie stats accumulated over the game
, _gameSelectedGoalie :: Maybe Int
-- ^ Index number of the selected 'Goalie'
, _goalieMinsPlayed :: Maybe Int
, _gameGoalieMinsPlayed :: Maybe Int
-- ^ The number of minutes the currently selected goalie played in
-- the game
, _goalsAllowed :: Maybe Int
, _gameGoalsAllowed :: Maybe Int
-- ^ The number of goals the currently selected goalie allowed in
-- the game
, _goaliesRecorded :: Bool
, _gameGoaliesRecorded :: Bool
-- ^ Set when the user confirms that all goalie info has been entered
, _gameGoalieAssigned :: Bool
-- ^ Set to 'True' when the goalie has been selected who will be
@ -642,13 +642,13 @@ newGameState = GameState
, _assistsBy = []
, _gamePlayerStats = M.empty
, _confirmGoalDataFlag = False
, _selectedPlayer = Nothing
, _pMinsRecorded = False
, _gameSelectedPlayer = Nothing
, _gamePMinsRecorded = False
, _gameGoalieStats = M.empty
, _gameSelectedGoalie = Nothing
, _goalieMinsPlayed = Nothing
, _goalsAllowed = Nothing
, _goaliesRecorded = False
, _gameGoalieMinsPlayed = Nothing
, _gameGoalsAllowed = Nothing
, _gameGoaliesRecorded = False
, _gameGoalieAssigned = False
}

View File

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