diff --git a/src/Mtlstats/Actions.hs b/src/Mtlstats/Actions.hs index 513c7f5..23acce7 100644 --- a/src/Mtlstats/Actions.hs +++ b/src/Mtlstats/Actions.hs @@ -35,6 +35,7 @@ module Mtlstats.Actions , recordGoalAssists , awardGoal , awardAssist + , resetGoalData ) where import Control.Monad.Trans.State (modify) @@ -161,9 +162,10 @@ recordGoalAssists ps = fromMaybe ps $ do & awardGoal goalId & (\s -> foldr awardAssist s assistIds) & progMode.gameStateL - %~ (goalBy .~ Nothing) - . (assistsBy .~ []) - . (pointsAccounted %~ succ) + %~ (goalBy .~ Nothing) + . (assistsBy .~ []) + . (pointsAccounted %~ succ) + . (confirmGoalDataFlag .~ False) -- | Awards a goal to a player awardGoal @@ -194,3 +196,10 @@ awardAssist n ps = ps & pYtd.psAssists %~ succ & pLifetime.psAssists %~ succ else p) . zip [0..] + +-- | Resets the entered data for the current goal +resetGoalData :: ProgState -> ProgState +resetGoalData ps = ps & progMode.gameStateL + %~ (goalBy .~ Nothing) + . (assistsBy .~ []) + . (confirmGoalDataFlag .~ False) diff --git a/src/Mtlstats/Control.hs b/src/Mtlstats/Control.hs index 8678ef2..bcb6cfb 100644 --- a/src/Mtlstats/Control.hs +++ b/src/Mtlstats/Control.hs @@ -36,6 +36,7 @@ import Mtlstats.Menu import Mtlstats.Prompt import Mtlstats.Report import Mtlstats.Types +import Mtlstats.Util -- | Reads the program state and returs the apropriate controller to -- run @@ -184,8 +185,9 @@ verifyDataC = Controller goalInput :: GameState -> Controller goalInput gs - | null (gs^.goalBy) = recordGoalC - | otherwise = recordAssistC + | null (gs^.goalBy ) = recordGoalC + | not (gs^.confirmGoalDataFlag) = recordAssistC + | otherwise = confirmGoalDataC recordGoalC :: Controller recordGoalC = Controller @@ -209,6 +211,36 @@ recordAssistC = Controller return True } +confirmGoalDataC :: Controller +confirmGoalDataC = Controller + { drawController = \s -> do + let + (game, goal) = gameGoal s + gs = s^.progMode.gameStateL + players = s^.database.dbPlayers + msg = unlines $ + [ " Game: " ++ padNum 2 game + , " Goal: " ++ show goal + , "Goal scored by: " ++ + playerSummary (fromJust $ gs^.goalBy >>= flip nth players) + ] ++ + map + (\pid -> " Assisted by: " ++ + playerSummary (fromJust $ nth pid players)) + (gs^.assistsBy) ++ + [ "" + , "Is the above information correct? (Y/N)" + ] + C.drawString msg + return C.CursorInvisible + , handleController = \e -> do + case ynHandler e of + Just True -> modify recordGoalAssists + Just False -> modify resetGoalData + Nothing -> return () + return True + } + reportC :: Controller reportC = Controller { drawController = \s -> do diff --git a/src/Mtlstats/Prompt.hs b/src/Mtlstats/Prompt.hs index 977f17b..dc17391 100644 --- a/src/Mtlstats/Prompt.hs +++ b/src/Mtlstats/Prompt.hs @@ -227,12 +227,12 @@ recordAssistPrompt game goal assist = selectPlayerPrompt ++ "Goal: " ++ show goal ++ "\n" ++ "Assist #" ++ show assist ++ ": " ) $ \case - Nothing -> modify recordGoalAssists + Nothing -> modify $ progMode.gameStateL.confirmGoalDataFlag .~ True Just n -> do modify $ progMode.gameStateL.assistsBy %~ (++[n]) nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy) when (nAssists >= maxAssists) $ - modify recordGoalAssists + modify $ progMode.gameStateL.confirmGoalDataFlag .~ True drawSimplePrompt :: String -> ProgState -> C.Update () drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer diff --git a/src/Mtlstats/Types.hs b/src/Mtlstats/Types.hs index 1c478b1..d438946 100644 --- a/src/Mtlstats/Types.hs +++ b/src/Mtlstats/Types.hs @@ -58,6 +58,7 @@ module Mtlstats.Types ( pointsAccounted, goalBy, assistsBy, + confirmGoalDataFlag, -- ** CreatePlayerState Lenses cpsNumber, cpsName, @@ -127,7 +128,8 @@ module Mtlstats.Types ( pPoints, playerSearch, playerSearchExact, - modifyPlayer + modifyPlayer, + playerSummary ) where import Control.Monad.Trans.State (StateT) @@ -187,32 +189,33 @@ instance Show ProgMode where -- | The game state data GameState = GameState - { _gameYear :: Maybe Int + { _gameYear :: Maybe Int -- ^ The year the game took place - , _gameMonth :: Maybe Int + , _gameMonth :: Maybe Int -- ^ The month the game took place - , _gameDay :: Maybe Int + , _gameDay :: Maybe Int -- ^ The day of the month the game took place - , _gameType :: Maybe GameType + , _gameType :: Maybe GameType -- ^ The type of game (home/away) - , _otherTeam :: String + , _otherTeam :: String -- ^ The name of the other team - , _homeScore :: Maybe Int + , _homeScore :: Maybe Int -- ^ The home team's score - , _awayScore :: Maybe Int + , _awayScore :: Maybe Int -- ^ The away team's score - , _overtimeFlag :: Maybe Bool + , _overtimeFlag :: Maybe Bool -- ^ Indicates whether or not the game went into overtime - , _dataVerified :: Bool + , _dataVerified :: Bool -- ^ Set to 'True' when the user confirms the entered data - , _pointsAccounted :: Int + , _pointsAccounted :: Int -- ^ The number of game points accounted for - , _goalBy :: Maybe Int + , _goalBy :: Maybe Int -- ^ The index number of the player who scored the most recently -- entered goal - , _assistsBy :: [Int] + , _assistsBy :: [Int] -- ^ The index numbers of the players who have assisted the most -- recently entered goal + , _confirmGoalDataFlag :: Bool } deriving (Eq, Show) -- | The type of game @@ -499,18 +502,19 @@ newProgState = ProgState -- | Constructor for a 'GameState' newGameState :: GameState newGameState = GameState - { _gameYear = Nothing - , _gameMonth = Nothing - , _gameDay = Nothing - , _gameType = Nothing - , _otherTeam = "" - , _homeScore = Nothing - , _awayScore = Nothing - , _overtimeFlag = Nothing - , _dataVerified = False - , _pointsAccounted = 0 - , _goalBy = Nothing - , _assistsBy = [] + { _gameYear = Nothing + , _gameMonth = Nothing + , _gameDay = Nothing + , _gameType = Nothing + , _otherTeam = "" + , _homeScore = Nothing + , _awayScore = Nothing + , _overtimeFlag = Nothing + , _dataVerified = False + , _pointsAccounted = 0 + , _goalBy = Nothing + , _assistsBy = [] + , _confirmGoalDataFlag = False } -- | Constructor for a 'CreatePlayerState' @@ -710,3 +714,8 @@ modifyPlayer f n = map (\p -> if p^.pName == n then f p else p) + +-- | Provides a short summary string for a player +playerSummary :: Player -> String +playerSummary p = + p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition diff --git a/test/ActionsSpec.hs b/test/ActionsSpec.hs index eae38b9..2818774 100644 --- a/test/ActionsSpec.hs +++ b/test/ActionsSpec.hs @@ -24,7 +24,7 @@ module ActionsSpec (spec) where import Control.Monad (replicateM) import Lens.Micro ((^.), (&), (.~), (?~), (%~)) import System.Random (randomRIO) -import Test.Hspec (Spec, context, describe, it, shouldBe, shouldNotBe) +import Test.Hspec (Spec, context, describe, it, runIO, shouldBe, shouldNotBe) import Mtlstats.Actions import Mtlstats.Types @@ -44,6 +44,7 @@ spec = describe "Mtlstats.Actions" $ do recordGoalAssistsSpec awardGoalSpec awardAssistSpec + resetGoalDataSpec startNewSeasonSpec :: Spec startNewSeasonSpec = describe "startNewSeason" $ do @@ -371,8 +372,9 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do = newProgState & database.dbPlayers .~ [joe, bob, steve, dave] & progMode.gameStateL - %~ (goalBy ?~ 0) - . (assistsBy .~ [1, 2]) + %~ (goalBy ?~ 0) + . (assistsBy .~ [1, 2]) + . (confirmGoalDataFlag .~ True) & recordGoalAssists mapM_ @@ -407,6 +409,9 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do it "should increment the pointsAccounted counter" $ ps^.progMode.gameStateL.pointsAccounted `shouldBe` 1 + it "should clear the confirmGoalDataFlag" $ + ps^.progMode.gameStateL.confirmGoalDataFlag `shouldBe` False + awardGoalSpec :: Spec awardGoalSpec = describe "awardGoal" $ do let @@ -513,6 +518,30 @@ awardAssistSpec = describe "awardAssist" $ do in it "should not change anything" $ ps'^.database.dbPlayers `shouldBe` ps^.database.dbPlayers +resetGoalDataSpec :: Spec +resetGoalDataSpec = describe "resetGoalData" $ do + players <- runIO $ replicateM 5 makePlayer + let + gs + = newGameState + & goalBy ?~ 1 + & assistsBy .~ [2, 3] + & confirmGoalDataFlag .~ True + ps + = newProgState + & database.dbPlayers .~ players + & progMode.gameStateL .~ gs + & resetGoalData + + it "should clear the goalBy value" $ + ps^.progMode.gameStateL.goalBy `shouldBe` Nothing + + it "should clear the assists by list" $ + ps^.progMode.gameStateL.assistsBy `shouldBe` [] + + it "should clear confirmGoalDataFlag" $ + ps^.progMode.gameStateL.confirmGoalDataFlag `shouldBe` False + makePlayer :: IO Player makePlayer = Player <$> makeNum diff --git a/test/TypesSpec.hs b/test/TypesSpec.hs index 13999c5..ad3b03d 100644 --- a/test/TypesSpec.hs +++ b/test/TypesSpec.hs @@ -58,6 +58,7 @@ spec = describe "Mtlstats.Types" $ do playerSearchSpec playerSearchExactSpec modifyPlayerSpec + playerSummarySpec Menu.spec playerSpec :: Spec @@ -578,6 +579,11 @@ modifyPlayerSpec = describe "modifyPlayer" $ mapM_ , ( "Sam", 0, 0, 0 ) ] +playerSummarySpec :: Spec +playerSummarySpec = describe "playerSummary" $ + it "should be \"Joe (2) center\"" $ + playerSummary joe `shouldBe` "Joe (2) center" + joe :: Player joe = newPlayer 2 "Joe" "center"