Merge pull request #22 from mtlstats/confirm-ga

Confirm goal/assist data
This commit is contained in:
Jonathan Lamothe 2019-10-02 02:09:07 -04:00 committed by GitHub
commit 9977a73da4
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
6 changed files with 120 additions and 35 deletions

View File

@ -35,6 +35,7 @@ module Mtlstats.Actions
, recordGoalAssists , recordGoalAssists
, awardGoal , awardGoal
, awardAssist , awardAssist
, resetGoalData
) where ) where
import Control.Monad.Trans.State (modify) import Control.Monad.Trans.State (modify)
@ -161,9 +162,10 @@ recordGoalAssists ps = fromMaybe ps $ do
& awardGoal goalId & awardGoal goalId
& (\s -> foldr awardAssist s assistIds) & (\s -> foldr awardAssist s assistIds)
& progMode.gameStateL & progMode.gameStateL
%~ (goalBy .~ Nothing) %~ (goalBy .~ Nothing)
. (assistsBy .~ []) . (assistsBy .~ [])
. (pointsAccounted %~ succ) . (pointsAccounted %~ succ)
. (confirmGoalDataFlag .~ False)
-- | Awards a goal to a player -- | Awards a goal to a player
awardGoal awardGoal
@ -194,3 +196,10 @@ awardAssist n ps = ps
& pYtd.psAssists %~ succ & pYtd.psAssists %~ succ
& pLifetime.psAssists %~ succ & pLifetime.psAssists %~ succ
else p) . zip [0..] 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)

View File

@ -36,6 +36,7 @@ import Mtlstats.Menu
import Mtlstats.Prompt import Mtlstats.Prompt
import Mtlstats.Report import Mtlstats.Report
import Mtlstats.Types import Mtlstats.Types
import Mtlstats.Util
-- | Reads the program state and returs the apropriate controller to -- | Reads the program state and returs the apropriate controller to
-- run -- run
@ -184,8 +185,9 @@ verifyDataC = Controller
goalInput :: GameState -> Controller goalInput :: GameState -> Controller
goalInput gs goalInput gs
| null (gs^.goalBy) = recordGoalC | null (gs^.goalBy ) = recordGoalC
| otherwise = recordAssistC | not (gs^.confirmGoalDataFlag) = recordAssistC
| otherwise = confirmGoalDataC
recordGoalC :: Controller recordGoalC :: Controller
recordGoalC = Controller recordGoalC = Controller
@ -209,6 +211,36 @@ recordAssistC = Controller
return True 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
reportC = Controller reportC = Controller
{ drawController = \s -> do { drawController = \s -> do

View File

@ -227,12 +227,12 @@ recordAssistPrompt game goal assist = selectPlayerPrompt
++ "Goal: " ++ show goal ++ "\n" ++ "Goal: " ++ show goal ++ "\n"
++ "Assist #" ++ show assist ++ ": " ++ "Assist #" ++ show assist ++ ": "
) $ \case ) $ \case
Nothing -> modify recordGoalAssists Nothing -> modify $ progMode.gameStateL.confirmGoalDataFlag .~ True
Just n -> do Just n -> do
modify $ progMode.gameStateL.assistsBy %~ (++[n]) modify $ progMode.gameStateL.assistsBy %~ (++[n])
nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy) nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy)
when (nAssists >= maxAssists) $ when (nAssists >= maxAssists) $
modify recordGoalAssists modify $ progMode.gameStateL.confirmGoalDataFlag .~ True
drawSimplePrompt :: String -> ProgState -> C.Update () drawSimplePrompt :: String -> ProgState -> C.Update ()
drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer

View File

@ -58,6 +58,7 @@ module Mtlstats.Types (
pointsAccounted, pointsAccounted,
goalBy, goalBy,
assistsBy, assistsBy,
confirmGoalDataFlag,
-- ** CreatePlayerState Lenses -- ** CreatePlayerState Lenses
cpsNumber, cpsNumber,
cpsName, cpsName,
@ -127,7 +128,8 @@ module Mtlstats.Types (
pPoints, pPoints,
playerSearch, playerSearch,
playerSearchExact, playerSearchExact,
modifyPlayer modifyPlayer,
playerSummary
) where ) where
import Control.Monad.Trans.State (StateT) import Control.Monad.Trans.State (StateT)
@ -187,32 +189,33 @@ instance Show ProgMode where
-- | The game state -- | The game state
data GameState = GameState data GameState = GameState
{ _gameYear :: Maybe Int { _gameYear :: Maybe Int
-- ^ The year the game took place -- ^ The year the game took place
, _gameMonth :: Maybe Int , _gameMonth :: Maybe Int
-- ^ The month the game took place -- ^ The month the game took place
, _gameDay :: Maybe Int , _gameDay :: Maybe Int
-- ^ The day of the month the game took place -- ^ The day of the month the game took place
, _gameType :: Maybe GameType , _gameType :: Maybe GameType
-- ^ The type of game (home/away) -- ^ The type of game (home/away)
, _otherTeam :: String , _otherTeam :: String
-- ^ The name of the other team -- ^ The name of the other team
, _homeScore :: Maybe Int , _homeScore :: Maybe Int
-- ^ The home team's score -- ^ The home team's score
, _awayScore :: Maybe Int , _awayScore :: Maybe Int
-- ^ The away team's score -- ^ The away team's score
, _overtimeFlag :: Maybe Bool , _overtimeFlag :: Maybe Bool
-- ^ Indicates whether or not the game went into overtime -- ^ Indicates whether or not the game went into overtime
, _dataVerified :: Bool , _dataVerified :: Bool
-- ^ Set to 'True' when the user confirms the entered data -- ^ Set to 'True' when the user confirms the entered data
, _pointsAccounted :: Int , _pointsAccounted :: Int
-- ^ The number of game points accounted for -- ^ The number of game points accounted for
, _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
, _confirmGoalDataFlag :: Bool
} deriving (Eq, Show) } deriving (Eq, Show)
-- | The type of game -- | The type of game
@ -499,18 +502,19 @@ 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 = []
, _confirmGoalDataFlag = False
} }
-- | Constructor for a 'CreatePlayerState' -- | Constructor for a 'CreatePlayerState'
@ -710,3 +714,8 @@ modifyPlayer f n = map
(\p -> if p^.pName == n (\p -> if p^.pName == n
then f p then f p
else p) else p)
-- | Provides a short summary string for a player
playerSummary :: Player -> String
playerSummary p =
p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition

View File

@ -24,7 +24,7 @@ module ActionsSpec (spec) where
import Control.Monad (replicateM) import Control.Monad (replicateM)
import Lens.Micro ((^.), (&), (.~), (?~), (%~)) import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import System.Random (randomRIO) 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.Actions
import Mtlstats.Types import Mtlstats.Types
@ -44,6 +44,7 @@ spec = describe "Mtlstats.Actions" $ do
recordGoalAssistsSpec recordGoalAssistsSpec
awardGoalSpec awardGoalSpec
awardAssistSpec awardAssistSpec
resetGoalDataSpec
startNewSeasonSpec :: Spec startNewSeasonSpec :: Spec
startNewSeasonSpec = describe "startNewSeason" $ do startNewSeasonSpec = describe "startNewSeason" $ do
@ -371,8 +372,9 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do
= newProgState = newProgState
& database.dbPlayers .~ [joe, bob, steve, dave] & database.dbPlayers .~ [joe, bob, steve, dave]
& progMode.gameStateL & progMode.gameStateL
%~ (goalBy ?~ 0) %~ (goalBy ?~ 0)
. (assistsBy .~ [1, 2]) . (assistsBy .~ [1, 2])
. (confirmGoalDataFlag .~ True)
& recordGoalAssists & recordGoalAssists
mapM_ mapM_
@ -407,6 +409,9 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do
it "should increment the pointsAccounted counter" $ it "should increment the pointsAccounted counter" $
ps^.progMode.gameStateL.pointsAccounted `shouldBe` 1 ps^.progMode.gameStateL.pointsAccounted `shouldBe` 1
it "should clear the confirmGoalDataFlag" $
ps^.progMode.gameStateL.confirmGoalDataFlag `shouldBe` False
awardGoalSpec :: Spec awardGoalSpec :: Spec
awardGoalSpec = describe "awardGoal" $ do awardGoalSpec = describe "awardGoal" $ do
let let
@ -513,6 +518,30 @@ awardAssistSpec = describe "awardAssist" $ do
in it "should not change anything" $ in it "should not change anything" $
ps'^.database.dbPlayers `shouldBe` ps^.database.dbPlayers 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 :: IO Player
makePlayer = Player makePlayer = Player
<$> makeNum <$> makeNum

View File

@ -58,6 +58,7 @@ spec = describe "Mtlstats.Types" $ do
playerSearchSpec playerSearchSpec
playerSearchExactSpec playerSearchExactSpec
modifyPlayerSpec modifyPlayerSpec
playerSummarySpec
Menu.spec Menu.spec
playerSpec :: Spec playerSpec :: Spec
@ -578,6 +579,11 @@ modifyPlayerSpec = describe "modifyPlayer" $ mapM_
, ( "Sam", 0, 0, 0 ) , ( "Sam", 0, 0, 0 )
] ]
playerSummarySpec :: Spec
playerSummarySpec = describe "playerSummary" $
it "should be \"Joe (2) center\"" $
playerSummary joe `shouldBe` "Joe (2) center"
joe :: Player joe :: Player
joe = newPlayer 2 "Joe" "center" joe = newPlayer 2 "Joe" "center"