Merge pull request #32 from mtlstats/game-goalie
Assign wins/losses/ties to goalies
This commit is contained in:
commit
f48de6d53a
|
@ -42,7 +42,6 @@ module Mtlstats.Actions
|
||||||
, awardAssist
|
, awardAssist
|
||||||
, resetGoalData
|
, resetGoalData
|
||||||
, assignPMins
|
, assignPMins
|
||||||
, recordGoalieStats
|
|
||||||
, backHome
|
, backHome
|
||||||
, scrollUp
|
, scrollUp
|
||||||
, scrollDown
|
, scrollDown
|
||||||
|
@ -265,7 +264,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))
|
||||||
|
@ -273,38 +272,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
|
|
||||||
recordGoalieStats :: ProgState -> ProgState
|
|
||||||
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
|
|
||||||
|
|
||||||
let
|
|
||||||
gameStats = M.findWithDefault newGoalieStats gid $ gs^.gameGoalieStats
|
|
||||||
bumpVal = if gameStats^.gsGames == 0
|
|
||||||
then 1
|
|
||||||
else 0
|
|
||||||
|
|
||||||
bumpStats gs = gs
|
|
||||||
& gsGames +~ bumpVal
|
|
||||||
& gsMinsPlayed +~ mins
|
|
||||||
& gsGoalsAllowed +~ goals
|
|
||||||
|
|
||||||
Just $ s
|
|
||||||
& progMode.gameStateL
|
|
||||||
%~ (gameGoalieStats %~ updateMap gid newGoalieStats bumpStats)
|
|
||||||
. (gameSelectedGoalie .~ Nothing)
|
|
||||||
. (goalieMinsPlayed .~ Nothing)
|
|
||||||
. (goalsAllowed .~ Nothing)
|
|
||||||
& database.dbGoalies
|
|
||||||
%~ modifyNth gid (\goalie -> goalie
|
|
||||||
& gYtd %~ bumpStats
|
|
||||||
& gLifetime %~ bumpStats)
|
|
||||||
|
|
||||||
-- | Resets the program state back to the main menu
|
-- | Resets the program state back to the main menu
|
||||||
backHome :: ProgState -> ProgState
|
backHome :: ProgState -> ProgState
|
||||||
|
|
|
@ -0,0 +1,108 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Mtlstats.Actions.GoalieInput
|
||||||
|
( finishGoalieEntry
|
||||||
|
, recordGoalieStats
|
||||||
|
, setGameGoalie
|
||||||
|
) where
|
||||||
|
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import Lens.Micro ((^.), (&), (.~), (%~), (+~))
|
||||||
|
|
||||||
|
import Mtlstats.Config
|
||||||
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
-- | Attempts to finish game goalie entry
|
||||||
|
finishGoalieEntry :: ProgState -> ProgState
|
||||||
|
finishGoalieEntry s = s & progMode.gameStateL.gameGoaliesRecorded
|
||||||
|
.~ not (null $ s^.progMode.gameStateL.gameGoalieStats)
|
||||||
|
|
||||||
|
-- | Records the goalie's game stats
|
||||||
|
recordGoalieStats :: ProgState -> ProgState
|
||||||
|
recordGoalieStats s = fromMaybe s $ do
|
||||||
|
let gs = s^.progMode.gameStateL
|
||||||
|
gid <- gs^.gameSelectedGoalie
|
||||||
|
goalie <- nth gid $ s^.database.dbGoalies
|
||||||
|
mins <- gs^.gameGoalieMinsPlayed
|
||||||
|
goals <- gs^.gameGoalsAllowed
|
||||||
|
|
||||||
|
let
|
||||||
|
gameStats = M.findWithDefault newGoalieStats gid $ gs^.gameGoalieStats
|
||||||
|
bumpVal = if gameStats^.gsGames == 0
|
||||||
|
then 1
|
||||||
|
else 0
|
||||||
|
|
||||||
|
bumpStats gs = gs
|
||||||
|
& gsGames +~ bumpVal
|
||||||
|
& gsMinsPlayed +~ mins
|
||||||
|
& gsGoalsAllowed +~ goals
|
||||||
|
|
||||||
|
tryFinish = if mins >= gameLength
|
||||||
|
then finishGoalieEntry
|
||||||
|
else id
|
||||||
|
|
||||||
|
Just $ s
|
||||||
|
& progMode.gameStateL
|
||||||
|
%~ (gameGoalieStats %~ updateMap gid newGoalieStats bumpStats)
|
||||||
|
. (gameSelectedGoalie .~ Nothing)
|
||||||
|
. (gameGoalieMinsPlayed .~ Nothing)
|
||||||
|
. (gameGoalsAllowed .~ Nothing)
|
||||||
|
& database.dbGoalies
|
||||||
|
%~ modifyNth gid (\goalie -> goalie
|
||||||
|
& gYtd %~ bumpStats
|
||||||
|
& gLifetime %~ bumpStats)
|
||||||
|
& tryFinish
|
||||||
|
|
||||||
|
-- | Records the win, loss, or tie to a specific 'Goalie'
|
||||||
|
setGameGoalie
|
||||||
|
:: Int
|
||||||
|
-- ^ The goalie's index
|
||||||
|
-> ProgState
|
||||||
|
-> ProgState
|
||||||
|
setGameGoalie gid s = fromMaybe s $ do
|
||||||
|
let gs = s^.progMode.gameStateL
|
||||||
|
won <- gameWon gs
|
||||||
|
lost <- gameLost gs
|
||||||
|
tied <- gs^.overtimeFlag
|
||||||
|
let
|
||||||
|
w = if won then 1 else 0
|
||||||
|
l = if lost then 1 else 0
|
||||||
|
t = if tied then 1 else 0
|
||||||
|
|
||||||
|
updateStats gs = gs
|
||||||
|
& gsWins +~ w
|
||||||
|
& gsLosses +~ l
|
||||||
|
& gsTies +~ t
|
||||||
|
|
||||||
|
updateGoalie g = g
|
||||||
|
& gYtd %~ updateStats
|
||||||
|
& gLifetime %~ updateStats
|
||||||
|
|
||||||
|
updateGameState gs = gs
|
||||||
|
& gameGoalieStats %~ updateMap gid newGoalieStats updateStats
|
||||||
|
& gameGoalieAssigned .~ True
|
||||||
|
|
||||||
|
Just $ s
|
||||||
|
& database.dbGoalies %~ modifyNth gid updateGoalie
|
||||||
|
& progMode.gameStateL %~ updateGameState
|
|
@ -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^.gameGoalieAssigned -> goalieInput s
|
||||||
| 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
|
||||||
|
|
|
@ -26,47 +26,38 @@ import Lens.Micro ((^.))
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
import Mtlstats.Format
|
import Mtlstats.Format
|
||||||
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Prompt
|
import Mtlstats.Prompt
|
||||||
|
import Mtlstats.Prompt.GoalieInput
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Util
|
import Mtlstats.Util
|
||||||
|
|
||||||
-- | The dispatcher for handling goalie input
|
-- | The dispatcher for handling goalie input
|
||||||
goalieInput :: GameState -> Controller
|
goalieInput :: ProgState -> Controller
|
||||||
goalieInput gs
|
goalieInput s = let
|
||||||
| null $ gs^.gameSelectedGoalie = selectGoalieC
|
gs = s^.progMode.gameStateL
|
||||||
| null $ gs^.goalieMinsPlayed = minsPlayedC
|
in if gs^.gameGoaliesRecorded
|
||||||
| otherwise = goalsAllowedC
|
then selectGameGoalieC s
|
||||||
|
else if null $ gs^.gameSelectedGoalie
|
||||||
|
then selectGoalieC
|
||||||
|
else if null $ gs^.gameGoalieMinsPlayed
|
||||||
|
then minsPlayedC
|
||||||
|
else goalsAllowedC
|
||||||
|
|
||||||
selectGoalieC :: Controller
|
selectGoalieC :: Controller
|
||||||
selectGoalieC = Controller
|
selectGoalieC = promptController selectGameGoaliePrompt
|
||||||
{ drawController = drawPrompt selectGameGoaliePrompt
|
|
||||||
, handleController = \e -> do
|
|
||||||
promptHandler selectGameGoaliePrompt e
|
|
||||||
return True
|
|
||||||
}
|
|
||||||
|
|
||||||
minsPlayedC :: Controller
|
minsPlayedC :: Controller
|
||||||
minsPlayedC = Controller
|
minsPlayedC = promptControllerWith header goalieMinsPlayedPrompt
|
||||||
{ drawController = \s -> do
|
|
||||||
C.drawString $ header s
|
|
||||||
drawPrompt goalieMinsPlayedPrompt s
|
|
||||||
, handleController = \e -> do
|
|
||||||
promptHandler goalieMinsPlayedPrompt e
|
|
||||||
return True
|
|
||||||
}
|
|
||||||
|
|
||||||
goalsAllowedC :: Controller
|
goalsAllowedC :: Controller
|
||||||
goalsAllowedC = Controller
|
goalsAllowedC = promptControllerWith header goalsAllowedPrompt
|
||||||
{ drawController = \s -> do
|
|
||||||
C.drawString $ header s
|
|
||||||
drawPrompt goalsAllowedPrompt s
|
|
||||||
, handleController = \e -> do
|
|
||||||
promptHandler goalsAllowedPrompt e
|
|
||||||
return True
|
|
||||||
}
|
|
||||||
|
|
||||||
header :: ProgState -> String
|
selectGameGoalieC :: ProgState -> Controller
|
||||||
header s = unlines
|
selectGameGoalieC = menuController . gameGoalieMenu
|
||||||
|
|
||||||
|
header :: ProgState -> C.Update ()
|
||||||
|
header s = C.drawString $ unlines
|
||||||
[ "*** GAME " ++ padNum 2 (s^.database.dbGames) ++ " ***"
|
[ "*** GAME " ++ padNum 2 (s^.database.dbGames) ++ " ***"
|
||||||
, fromMaybe "" $ do
|
, fromMaybe "" $ do
|
||||||
n <- s^.progMode.gameStateL.gameSelectedGoalie
|
n <- s^.progMode.gameStateL.gameSelectedGoalie
|
||||||
|
|
|
@ -21,6 +21,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Mtlstats.Menu (
|
module Mtlstats.Menu (
|
||||||
-- * Menu Functions
|
-- * Menu Functions
|
||||||
|
menuController,
|
||||||
drawMenu,
|
drawMenu,
|
||||||
menuHandler,
|
menuHandler,
|
||||||
-- * Menus
|
-- * Menus
|
||||||
|
@ -28,13 +29,16 @@ module Mtlstats.Menu (
|
||||||
newSeasonMenu,
|
newSeasonMenu,
|
||||||
gameMonthMenu,
|
gameMonthMenu,
|
||||||
gameTypeMenu,
|
gameTypeMenu,
|
||||||
editPlayerMenu
|
editPlayerMenu,
|
||||||
|
gameGoalieMenu
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Trans.State (gets, modify)
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Aeson (encodeFile)
|
import Data.Aeson (encodeFile)
|
||||||
import Data.Char (toUpper)
|
import Data.Char (toUpper)
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import Data.Maybe (mapMaybe)
|
||||||
import Lens.Micro ((^.), (.~), (?~))
|
import Lens.Micro ((^.), (.~), (?~))
|
||||||
import Lens.Micro.Extras (view)
|
import Lens.Micro.Extras (view)
|
||||||
import System.EasyFile
|
import System.EasyFile
|
||||||
|
@ -45,9 +49,20 @@ import System.EasyFile
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
import Mtlstats.Actions
|
import Mtlstats.Actions
|
||||||
|
import qualified Mtlstats.Actions.GoalieInput as GI
|
||||||
import Mtlstats.Config
|
import Mtlstats.Config
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Types.Menu
|
import Mtlstats.Types.Menu
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
-- | Generates a simple 'Controller' for a Menu
|
||||||
|
menuController :: Menu () -> Controller
|
||||||
|
menuController menu = Controller
|
||||||
|
{ drawController = const $ drawMenu menu
|
||||||
|
, handleController = \e -> do
|
||||||
|
menuHandler menu e
|
||||||
|
return True
|
||||||
|
}
|
||||||
|
|
||||||
-- | The draw function for a 'Menu'
|
-- | The draw function for a 'Menu'
|
||||||
drawMenu :: Menu a -> C.Update C.CursorMode
|
drawMenu :: Menu a -> C.Update C.CursorMode
|
||||||
|
@ -142,3 +157,18 @@ editPlayerMenu = Menu "*** EDIT PLAYER ***" () $ map
|
||||||
, ( '9', "Lifetime penalty mins", Just EPLtPMin )
|
, ( '9', "Lifetime penalty mins", Just EPLtPMin )
|
||||||
, ( '0', "Finished editing", Nothing )
|
, ( '0', "Finished editing", Nothing )
|
||||||
]
|
]
|
||||||
|
|
||||||
|
-- | Game goalie selection menu
|
||||||
|
gameGoalieMenu :: ProgState -> Menu ()
|
||||||
|
gameGoalieMenu s = let
|
||||||
|
title = "Which goalie should get credit for the game?"
|
||||||
|
gids = map fst $ M.toList $ s^.progMode.gameStateL.gameGoalieStats
|
||||||
|
goalies = mapMaybe
|
||||||
|
(\n -> do
|
||||||
|
goalie <- nth n $ s^.database.dbGoalies
|
||||||
|
Just (n, goalie))
|
||||||
|
gids
|
||||||
|
in Menu title () $ map
|
||||||
|
(\(ch, (gid, goalie)) -> MenuItem ch (goalieSummary goalie) $
|
||||||
|
modify $ GI.setGameGoalie gid) $
|
||||||
|
zip ['1'..] goalies
|
||||||
|
|
|
@ -25,6 +25,8 @@ module Mtlstats.Prompt (
|
||||||
-- * Prompt Functions
|
-- * Prompt Functions
|
||||||
drawPrompt,
|
drawPrompt,
|
||||||
promptHandler,
|
promptHandler,
|
||||||
|
promptControllerWith,
|
||||||
|
promptController,
|
||||||
strPrompt,
|
strPrompt,
|
||||||
numPrompt,
|
numPrompt,
|
||||||
selectPrompt,
|
selectPrompt,
|
||||||
|
@ -37,17 +39,14 @@ module Mtlstats.Prompt (
|
||||||
playerNumPrompt,
|
playerNumPrompt,
|
||||||
playerNamePrompt,
|
playerNamePrompt,
|
||||||
playerPosPrompt,
|
playerPosPrompt,
|
||||||
|
goalieNumPrompt,
|
||||||
|
goalieNamePrompt,
|
||||||
selectPlayerPrompt,
|
selectPlayerPrompt,
|
||||||
selectGoaliePrompt,
|
selectGoaliePrompt,
|
||||||
recordGoalPrompt,
|
recordGoalPrompt,
|
||||||
recordAssistPrompt,
|
recordAssistPrompt,
|
||||||
pMinPlayerPrompt,
|
pMinPlayerPrompt,
|
||||||
assignPMinsPrompt,
|
assignPMinsPrompt,
|
||||||
goalieNumPrompt,
|
|
||||||
goalieNamePrompt,
|
|
||||||
selectGameGoaliePrompt,
|
|
||||||
goalieMinsPlayedPrompt,
|
|
||||||
goalsAllowedPrompt,
|
|
||||||
playerToEditPrompt
|
playerToEditPrompt
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -90,6 +89,31 @@ promptHandler p (C.EventSpecialKey k) =
|
||||||
promptSpecialKey p k
|
promptSpecialKey p k
|
||||||
promptHandler _ _ = return ()
|
promptHandler _ _ = return ()
|
||||||
|
|
||||||
|
-- | Builds a controller out of a prompt with a header
|
||||||
|
promptControllerWith
|
||||||
|
:: (ProgState -> C.Update ())
|
||||||
|
-- ^ The header
|
||||||
|
-> Prompt
|
||||||
|
-- ^ The prompt to use
|
||||||
|
-> Controller
|
||||||
|
-- ^ The resulting controller
|
||||||
|
promptControllerWith header prompt = Controller
|
||||||
|
{ drawController = \s -> do
|
||||||
|
header s
|
||||||
|
drawPrompt prompt s
|
||||||
|
, handleController = \e -> do
|
||||||
|
promptHandler prompt e
|
||||||
|
return True
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Builds a controller out of a prompt
|
||||||
|
promptController
|
||||||
|
:: Prompt
|
||||||
|
-- ^ The prompt to use
|
||||||
|
-> Controller
|
||||||
|
-- ^ The resulting controller
|
||||||
|
promptController = promptControllerWith (const $ return ())
|
||||||
|
|
||||||
-- | Builds a string prompt
|
-- | Builds a string prompt
|
||||||
strPrompt
|
strPrompt
|
||||||
:: String
|
:: String
|
||||||
|
@ -195,6 +219,16 @@ playerPosPrompt :: Prompt
|
||||||
playerPosPrompt = strPrompt "Player position: " $
|
playerPosPrompt = strPrompt "Player position: " $
|
||||||
modify . (progMode.createPlayerStateL.cpsPosition .~)
|
modify . (progMode.createPlayerStateL.cpsPosition .~)
|
||||||
|
|
||||||
|
-- | Prompts tor the goalie's number
|
||||||
|
goalieNumPrompt :: Prompt
|
||||||
|
goalieNumPrompt = numPrompt "Goalie number: " $
|
||||||
|
modify . (progMode.createGoalieStateL.cgsNumber ?~)
|
||||||
|
|
||||||
|
-- | Prompts for the goalie's name
|
||||||
|
goalieNamePrompt :: Prompt
|
||||||
|
goalieNamePrompt = strPrompt "Goalie name: " $
|
||||||
|
modify . (progMode.createGoalieStateL.cgsName .~)
|
||||||
|
|
||||||
-- | Selects a player (creating one if necessary)
|
-- | Selects a player (creating one if necessary)
|
||||||
selectPlayerPrompt
|
selectPlayerPrompt
|
||||||
:: String
|
:: String
|
||||||
|
@ -289,45 +323,14 @@ 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
|
||||||
assignPMinsPrompt = numPrompt "Penalty minutes: " $
|
assignPMinsPrompt = numPrompt "Penalty minutes: " $
|
||||||
modify . assignPMins
|
modify . assignPMins
|
||||||
|
|
||||||
-- | Prompts tor the goalie's number
|
|
||||||
goalieNumPrompt :: Prompt
|
|
||||||
goalieNumPrompt = numPrompt "Goalie number: " $
|
|
||||||
modify . (progMode.createGoalieStateL.cgsNumber ?~)
|
|
||||||
|
|
||||||
-- | Prompts for the goalie's name
|
|
||||||
goalieNamePrompt :: Prompt
|
|
||||||
goalieNamePrompt = strPrompt "Goalie name: " $
|
|
||||||
modify . (progMode.createGoalieStateL.cgsName .~)
|
|
||||||
|
|
||||||
-- | Prompts for a goalie who played in the game
|
|
||||||
selectGameGoaliePrompt :: Prompt
|
|
||||||
selectGameGoaliePrompt = selectGoaliePrompt "Which goalie played this game: " $
|
|
||||||
\case
|
|
||||||
Nothing -> modify $ progMode.gameStateL.goaliesRecorded .~ True
|
|
||||||
Just n -> modify $ progMode.gameStateL.gameSelectedGoalie ?~ n
|
|
||||||
|
|
||||||
-- | Prompts for the number of minutes the goalie has played
|
|
||||||
goalieMinsPlayedPrompt :: Prompt
|
|
||||||
goalieMinsPlayedPrompt = numPrompt "Minutes played: " $
|
|
||||||
modify . (progMode.gameStateL.goalieMinsPlayed ?~)
|
|
||||||
|
|
||||||
-- | 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)
|
|
||||||
when (mins >= gameLength) $
|
|
||||||
modify $ progMode.gameStateL.goaliesRecorded .~ True
|
|
||||||
modify recordGoalieStats
|
|
||||||
|
|
||||||
playerToEditPrompt :: Prompt
|
playerToEditPrompt :: Prompt
|
||||||
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
|
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
|
||||||
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
|
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
|
||||||
|
|
|
@ -0,0 +1,56 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
|
||||||
|
module Mtlstats.Prompt.GoalieInput
|
||||||
|
( selectGameGoaliePrompt
|
||||||
|
, goalieMinsPlayedPrompt
|
||||||
|
, goalsAllowedPrompt
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Monad (when)
|
||||||
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import Lens.Micro ((^.), (.~), (?~))
|
||||||
|
|
||||||
|
import Mtlstats.Actions.GoalieInput
|
||||||
|
import Mtlstats.Config
|
||||||
|
import Mtlstats.Prompt
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
-- | Prompts for a goalie who played in the game
|
||||||
|
selectGameGoaliePrompt :: Prompt
|
||||||
|
selectGameGoaliePrompt = selectGoaliePrompt "Which goalie played this game: " $
|
||||||
|
\case
|
||||||
|
Nothing -> modify finishGoalieEntry
|
||||||
|
Just n -> modify $ progMode.gameStateL.gameSelectedGoalie ?~ n
|
||||||
|
|
||||||
|
-- | Prompts for the number of minutes the goalie has played
|
||||||
|
goalieMinsPlayedPrompt :: Prompt
|
||||||
|
goalieMinsPlayedPrompt = numPrompt "Minutes played: " $
|
||||||
|
modify . (progMode.gameStateL.gameGoalieMinsPlayed ?~)
|
||||||
|
|
||||||
|
-- | Prompts for the number of goals the goalie allowed
|
||||||
|
goalsAllowedPrompt :: Prompt
|
||||||
|
goalsAllowedPrompt = numPrompt "Goals allowed: " $ \n -> do
|
||||||
|
modify (progMode.gameStateL.gameGoalsAllowed ?~ n)
|
||||||
|
modify recordGoalieStats
|
|
@ -67,13 +67,14 @@ module Mtlstats.Types (
|
||||||
assistsBy,
|
assistsBy,
|
||||||
gamePlayerStats,
|
gamePlayerStats,
|
||||||
confirmGoalDataFlag,
|
confirmGoalDataFlag,
|
||||||
selectedPlayer,
|
gameSelectedPlayer,
|
||||||
pMinsRecorded,
|
gamePMinsRecorded,
|
||||||
gameGoalieStats,
|
gameGoalieStats,
|
||||||
gameSelectedGoalie,
|
gameSelectedGoalie,
|
||||||
goalieMinsPlayed,
|
gameGoalieMinsPlayed,
|
||||||
goalsAllowed,
|
gameGoalsAllowed,
|
||||||
goaliesRecorded,
|
gameGoaliesRecorded,
|
||||||
|
gameGoalieAssigned,
|
||||||
-- ** CreatePlayerState Lenses
|
-- ** CreatePlayerState Lenses
|
||||||
cpsNumber,
|
cpsNumber,
|
||||||
cpsName,
|
cpsName,
|
||||||
|
@ -251,29 +252,32 @@ 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
|
||||||
|
-- ^ Set to 'True' when the goalie has been selected who will be
|
||||||
|
-- given the win/loss/tie
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
-- | The type of game
|
-- | The type of game
|
||||||
|
@ -624,27 +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
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Constructor for a 'CreatePlayerState'
|
-- | Constructor for a 'CreatePlayerState'
|
||||||
|
|
|
@ -0,0 +1,291 @@
|
||||||
|
{-
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 2019 Rhéal Lamothe
|
||||||
|
<rheal.lamothe@gmail.com>
|
||||||
|
|
||||||
|
This program is free software: you can redistribute it and/or modify
|
||||||
|
it under the terms of the GNU General Public License as published by
|
||||||
|
the Free Software Foundation, either version 3 of the License, or (at
|
||||||
|
your option) any later version.
|
||||||
|
|
||||||
|
This program is distributed in the hope that it will be useful, but
|
||||||
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||||
|
General Public License for more details.
|
||||||
|
|
||||||
|
You should have received a copy of the GNU General Public License
|
||||||
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Actions.GoalieInputSpec (spec) where
|
||||||
|
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import Data.Maybe (fromJust)
|
||||||
|
import Lens.Micro ((^.), (&), (.~), (?~))
|
||||||
|
import Test.Hspec (Spec, context, describe, it, shouldBe)
|
||||||
|
|
||||||
|
import Mtlstats.Actions.GoalieInput
|
||||||
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
import qualified TypesSpec as TS
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Mtlstats.Actions.GoalieInput" $ do
|
||||||
|
finishGoalieEntrySpec
|
||||||
|
recordGoalieStatsSpec
|
||||||
|
setGameGoalieSpec
|
||||||
|
|
||||||
|
finishGoalieEntrySpec :: Spec
|
||||||
|
finishGoalieEntrySpec = describe "finishGoalieEntry" $ do
|
||||||
|
let
|
||||||
|
progState stats = newProgState
|
||||||
|
& progMode.gameStateL.gameGoalieStats .~ stats
|
||||||
|
& finishGoalieEntry
|
||||||
|
|
||||||
|
context "no goalie data" $
|
||||||
|
it "should not set goaliesRecorded" $ let
|
||||||
|
s = progState M.empty
|
||||||
|
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.gameGoaliesRecorded `shouldBe` True
|
||||||
|
|
||||||
|
recordGoalieStatsSpec :: Spec
|
||||||
|
recordGoalieStatsSpec = describe "recordGoalieStats" $ let
|
||||||
|
goalieStats games mins goals = newGoalieStats
|
||||||
|
& gsGames .~ games
|
||||||
|
& gsMinsPlayed .~ mins
|
||||||
|
& gsGoalsAllowed .~ goals
|
||||||
|
|
||||||
|
joe = newGoalie 2 "Joe"
|
||||||
|
& gYtd .~ goalieStats 10 11 12
|
||||||
|
& gLifetime .~ goalieStats 20 21 22
|
||||||
|
|
||||||
|
bob = newGoalie 3 "Bob"
|
||||||
|
& gYtd .~ goalieStats 30 31 32
|
||||||
|
& gLifetime .~ goalieStats 40 41 42
|
||||||
|
|
||||||
|
gameState n mins goals = newGameState
|
||||||
|
& gameGoalieStats .~ M.fromList [(1, goalieStats 1 2 3)]
|
||||||
|
& gameSelectedGoalie .~ n
|
||||||
|
& gameGoalieMinsPlayed .~ mins
|
||||||
|
& gameGoalsAllowed .~ goals
|
||||||
|
|
||||||
|
progState n mins goals = newProgState
|
||||||
|
& database.dbGoalies .~ [joe, bob]
|
||||||
|
& progMode.gameStateL .~ gameState n mins goals
|
||||||
|
|
||||||
|
in mapM_
|
||||||
|
(\(name, gid, mins, goals, joeData, bobData, reset) -> let
|
||||||
|
s = recordGoalieStats $ progState gid mins goals
|
||||||
|
in context name $ do
|
||||||
|
|
||||||
|
mapM_
|
||||||
|
(\( name
|
||||||
|
, gid
|
||||||
|
, ( gGames
|
||||||
|
, gMins
|
||||||
|
, gGoals
|
||||||
|
, ytdGames
|
||||||
|
, ytdMins
|
||||||
|
, ytdGoals
|
||||||
|
, ltGames
|
||||||
|
, ltMins
|
||||||
|
, ltGoals
|
||||||
|
)
|
||||||
|
) -> context name $ do
|
||||||
|
let
|
||||||
|
gs = s^.progMode.gameStateL.gameGoalieStats
|
||||||
|
game = M.findWithDefault newGoalieStats gid gs
|
||||||
|
goalie = fromJust $ nth gid $ s^.database.dbGoalies
|
||||||
|
ytd = goalie^.gYtd
|
||||||
|
lt = goalie^.gLifetime
|
||||||
|
|
||||||
|
context "game" $
|
||||||
|
game `TS.compareTest` goalieStats gGames gMins gGoals
|
||||||
|
|
||||||
|
context "year-to-date" $
|
||||||
|
ytd `TS.compareTest` goalieStats ytdGames ytdMins ytdGoals
|
||||||
|
|
||||||
|
context "lifetime" $
|
||||||
|
lt `TS.compareTest` goalieStats ltGames ltMins ltGoals)
|
||||||
|
|
||||||
|
[ ( "checking Joe", 0, joeData )
|
||||||
|
, ( "checking Bob", 1, bobData )
|
||||||
|
]
|
||||||
|
|
||||||
|
context "selected goalie" $ let
|
||||||
|
expected = if reset then Nothing else gid
|
||||||
|
in it ("should be " ++ show expected) $
|
||||||
|
(s^.progMode.gameStateL.gameSelectedGoalie) `shouldBe` expected
|
||||||
|
|
||||||
|
context "minutes played" $ let
|
||||||
|
expected = if reset then Nothing else mins
|
||||||
|
in it ("should be " ++ show 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.gameGoalsAllowed) `shouldBe` expected)
|
||||||
|
|
||||||
|
[ ( "updating Joe"
|
||||||
|
, Just 0
|
||||||
|
, Just 1
|
||||||
|
, Just 2
|
||||||
|
, (1, 1, 2, 11, 12, 14, 21, 22, 24)
|
||||||
|
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
||||||
|
, True
|
||||||
|
)
|
||||||
|
, ( "updating Bob"
|
||||||
|
, Just 1
|
||||||
|
, Just 1
|
||||||
|
, Just 2
|
||||||
|
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
||||||
|
, (1, 3, 5, 30, 32, 34, 40, 42, 44)
|
||||||
|
, True
|
||||||
|
)
|
||||||
|
, ( "goalie out of bounds"
|
||||||
|
, Just 2
|
||||||
|
, Just 1
|
||||||
|
, Just 2
|
||||||
|
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
||||||
|
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
||||||
|
, False
|
||||||
|
)
|
||||||
|
, ( "missing goalie"
|
||||||
|
, Nothing
|
||||||
|
, Just 1
|
||||||
|
, Just 2
|
||||||
|
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
||||||
|
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
||||||
|
, False
|
||||||
|
)
|
||||||
|
, ( "missing minutes"
|
||||||
|
, Just 0
|
||||||
|
, Nothing
|
||||||
|
, Just 1
|
||||||
|
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
||||||
|
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
||||||
|
, False
|
||||||
|
)
|
||||||
|
, ( "missing goals"
|
||||||
|
, Just 0
|
||||||
|
, Just 1
|
||||||
|
, Nothing
|
||||||
|
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
||||||
|
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
||||||
|
, False
|
||||||
|
)
|
||||||
|
]
|
||||||
|
|
||||||
|
setGameGoalieSpec :: Spec
|
||||||
|
setGameGoalieSpec = describe "setGameGoalie" $ let
|
||||||
|
|
||||||
|
goalieStats w l t = newGoalieStats
|
||||||
|
& gsWins .~ w
|
||||||
|
& gsLosses .~ l
|
||||||
|
& gsTies .~ t
|
||||||
|
|
||||||
|
bob = newGoalie 2 "Bob"
|
||||||
|
& gYtd .~ goalieStats 10 11 12
|
||||||
|
& gLifetime .~ goalieStats 20 21 22
|
||||||
|
|
||||||
|
joe = newGoalie 3 "Joe"
|
||||||
|
& gYtd .~ goalieStats 30 31 32
|
||||||
|
& gLifetime .~ goalieStats 40 41 42
|
||||||
|
|
||||||
|
gameState h a ot = newGameState
|
||||||
|
& gameType ?~ HomeGame
|
||||||
|
& homeScore ?~ h
|
||||||
|
& awayScore ?~ a
|
||||||
|
& overtimeFlag ?~ ot
|
||||||
|
|
||||||
|
winningGame = gameState 1 0 False
|
||||||
|
losingGame = gameState 0 1 False
|
||||||
|
tiedGame = gameState 0 1 True
|
||||||
|
|
||||||
|
in mapM_
|
||||||
|
(\(label, gameState, gid, bobData, joeData) -> context label $ let
|
||||||
|
|
||||||
|
progState = newProgState
|
||||||
|
& database.dbGoalies .~ [bob, joe]
|
||||||
|
& progMode.gameStateL .~ gameState
|
||||||
|
& setGameGoalie gid
|
||||||
|
|
||||||
|
in mapM_
|
||||||
|
(\( label
|
||||||
|
, gid
|
||||||
|
, ( gWins
|
||||||
|
, gLosses
|
||||||
|
, gTies
|
||||||
|
, ytdWins
|
||||||
|
, ytdLosses
|
||||||
|
, ytdTies
|
||||||
|
, ltWins
|
||||||
|
, ltLosses
|
||||||
|
, ltTies
|
||||||
|
)
|
||||||
|
) -> context label $ do
|
||||||
|
let
|
||||||
|
goalie = (progState^.database.dbGoalies) !! gid
|
||||||
|
gameStats = progState^.progMode.gameStateL.gameGoalieStats
|
||||||
|
game = M.findWithDefault newGoalieStats gid gameStats
|
||||||
|
ytd = goalie^.gYtd
|
||||||
|
lifetime = goalie^.gLifetime
|
||||||
|
|
||||||
|
mapM_
|
||||||
|
(\(label, expected, actual) -> context label $
|
||||||
|
expected `TS.compareTest` actual)
|
||||||
|
[ ( "game stats", game, goalieStats gWins gLosses gTies )
|
||||||
|
, ( "YTD stats", ytd, goalieStats ytdWins ytdLosses ytdTies )
|
||||||
|
, ( "lifetime stats", lifetime, goalieStats ltWins ltLosses ltTies )
|
||||||
|
]
|
||||||
|
|
||||||
|
it "should set the gameGoalieAssigned flag" $
|
||||||
|
progState^.progMode.gameStateL.gameGoalieAssigned `shouldBe` True)
|
||||||
|
[ ( "checking Bob", 0, bobData )
|
||||||
|
, ( "checking Joe", 1, joeData )
|
||||||
|
])
|
||||||
|
[ ( "Bob wins"
|
||||||
|
, winningGame
|
||||||
|
, 0
|
||||||
|
, ( 1, 0, 0, 11, 11, 12, 21, 21, 22 )
|
||||||
|
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 )
|
||||||
|
)
|
||||||
|
, ( "Bob loses"
|
||||||
|
, losingGame
|
||||||
|
, 0
|
||||||
|
, ( 0, 1, 0, 10, 12, 12, 20, 22, 22 )
|
||||||
|
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 )
|
||||||
|
)
|
||||||
|
, ( "Bob ties"
|
||||||
|
, tiedGame
|
||||||
|
, 0
|
||||||
|
, ( 0, 0, 1, 10, 11, 13, 20, 21, 23 )
|
||||||
|
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 )
|
||||||
|
)
|
||||||
|
, ( "Joe wins"
|
||||||
|
, winningGame
|
||||||
|
, 1
|
||||||
|
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 )
|
||||||
|
, ( 1, 0, 0, 31, 31, 32, 41, 41, 42 )
|
||||||
|
)
|
||||||
|
, ( "Joe loses"
|
||||||
|
, losingGame
|
||||||
|
, 1
|
||||||
|
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 )
|
||||||
|
, ( 0, 1, 0, 30, 32, 32, 40, 42, 42 )
|
||||||
|
)
|
||||||
|
, ( "Joe ties"
|
||||||
|
, tiedGame
|
||||||
|
, 1
|
||||||
|
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 )
|
||||||
|
, ( 0, 0, 1, 30, 31, 33, 40, 41, 43 )
|
||||||
|
)
|
||||||
|
]
|
|
@ -43,6 +43,7 @@ import Mtlstats.Actions
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Util
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
import qualified Actions.GoalieInputSpec as GoalieInput
|
||||||
import qualified TypesSpec as TS
|
import qualified TypesSpec as TS
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
|
@ -67,10 +68,10 @@ spec = describe "Mtlstats.Actions" $ do
|
||||||
awardAssistSpec
|
awardAssistSpec
|
||||||
resetGoalDataSpec
|
resetGoalDataSpec
|
||||||
assignPMinsSpec
|
assignPMinsSpec
|
||||||
recordGoalieStatsSpec
|
|
||||||
backHomeSpec
|
backHomeSpec
|
||||||
scrollUpSpec
|
scrollUpSpec
|
||||||
scrollDownSpec
|
scrollDownSpec
|
||||||
|
GoalieInput.spec
|
||||||
|
|
||||||
startNewSeasonSpec :: Spec
|
startNewSeasonSpec :: Spec
|
||||||
startNewSeasonSpec = describe "startNewSeason" $ do
|
startNewSeasonSpec = describe "startNewSeason" $ do
|
||||||
|
@ -637,7 +638,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) ->
|
||||||
|
@ -669,7 +670,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 )
|
||||||
|
@ -678,135 +679,6 @@ assignPMinsSpec = describe "assignPMins" $ let
|
||||||
, ( Nothing, 4, 3, 2, 6, 5, 0 )
|
, ( Nothing, 4, 3, 2, 6, 5, 0 )
|
||||||
]
|
]
|
||||||
|
|
||||||
recordGoalieStatsSpec :: Spec
|
|
||||||
recordGoalieStatsSpec = describe "recordGoalieStats" $ let
|
|
||||||
goalieStats games mins goals = newGoalieStats
|
|
||||||
& gsGames .~ games
|
|
||||||
& gsMinsPlayed .~ mins
|
|
||||||
& gsGoalsAllowed .~ goals
|
|
||||||
|
|
||||||
joe = newGoalie 2 "Joe"
|
|
||||||
& gYtd .~ goalieStats 10 11 12
|
|
||||||
& gLifetime .~ goalieStats 20 21 22
|
|
||||||
|
|
||||||
bob = newGoalie 3 "Bob"
|
|
||||||
& gYtd .~ goalieStats 30 31 32
|
|
||||||
& gLifetime .~ goalieStats 40 41 42
|
|
||||||
|
|
||||||
gameState n mins goals = newGameState
|
|
||||||
& gameGoalieStats .~ M.fromList [(1, goalieStats 1 2 3)]
|
|
||||||
& gameSelectedGoalie .~ n
|
|
||||||
& goalieMinsPlayed .~ mins
|
|
||||||
& goalsAllowed .~ goals
|
|
||||||
|
|
||||||
progState n mins goals = newProgState
|
|
||||||
& database.dbGoalies .~ [joe, bob]
|
|
||||||
& progMode.gameStateL .~ gameState n mins goals
|
|
||||||
|
|
||||||
in mapM_
|
|
||||||
(\(name, gid, mins, goals, joeData, bobData, reset) -> let
|
|
||||||
s = recordGoalieStats $ progState gid mins goals
|
|
||||||
in context name $ do
|
|
||||||
|
|
||||||
mapM_
|
|
||||||
(\( name
|
|
||||||
, gid
|
|
||||||
, ( gGames
|
|
||||||
, gMins
|
|
||||||
, gGoals
|
|
||||||
, ytdGames
|
|
||||||
, ytdMins
|
|
||||||
, ytdGoals
|
|
||||||
, ltGames
|
|
||||||
, ltMins
|
|
||||||
, ltGoals
|
|
||||||
)
|
|
||||||
) -> context name $ do
|
|
||||||
let
|
|
||||||
gs = s^.progMode.gameStateL.gameGoalieStats
|
|
||||||
game = M.findWithDefault newGoalieStats gid gs
|
|
||||||
goalie = fromJust $ nth gid $ s^.database.dbGoalies
|
|
||||||
ytd = goalie^.gYtd
|
|
||||||
lt = goalie^.gLifetime
|
|
||||||
|
|
||||||
context "game" $
|
|
||||||
game `TS.compareTest` goalieStats gGames gMins gGoals
|
|
||||||
|
|
||||||
context "year-to-date" $
|
|
||||||
ytd `TS.compareTest` goalieStats ytdGames ytdMins ytdGoals
|
|
||||||
|
|
||||||
context "lifetime" $
|
|
||||||
lt `TS.compareTest` goalieStats ltGames ltMins ltGoals)
|
|
||||||
|
|
||||||
[ ( "checking Joe", 0, joeData )
|
|
||||||
, ( "checking Bob", 1, bobData )
|
|
||||||
]
|
|
||||||
|
|
||||||
context "selected goalie" $ let
|
|
||||||
expected = if reset then Nothing else gid
|
|
||||||
in it ("should be " ++ show expected) $
|
|
||||||
(s^.progMode.gameStateL.gameSelectedGoalie) `shouldBe` expected
|
|
||||||
|
|
||||||
context "minutes played" $ let
|
|
||||||
expected = if reset then Nothing else mins
|
|
||||||
in it ("should be " ++ show expected) $
|
|
||||||
(s^.progMode.gameStateL.goalieMinsPlayed) `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)
|
|
||||||
|
|
||||||
[ ( "updating Joe"
|
|
||||||
, Just 0
|
|
||||||
, Just 1
|
|
||||||
, Just 2
|
|
||||||
, (1, 1, 2, 11, 12, 14, 21, 22, 24)
|
|
||||||
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
|
||||||
, True
|
|
||||||
)
|
|
||||||
, ( "updating Bob"
|
|
||||||
, Just 1
|
|
||||||
, Just 1
|
|
||||||
, Just 2
|
|
||||||
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
|
||||||
, (1, 3, 5, 30, 32, 34, 40, 42, 44)
|
|
||||||
, True
|
|
||||||
)
|
|
||||||
, ( "goalie out of bounds"
|
|
||||||
, Just 2
|
|
||||||
, Just 1
|
|
||||||
, Just 2
|
|
||||||
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
|
||||||
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
|
||||||
, False
|
|
||||||
)
|
|
||||||
, ( "missing goalie"
|
|
||||||
, Nothing
|
|
||||||
, Just 1
|
|
||||||
, Just 2
|
|
||||||
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
|
||||||
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
|
||||||
, False
|
|
||||||
)
|
|
||||||
, ( "missing minutes"
|
|
||||||
, Just 0
|
|
||||||
, Nothing
|
|
||||||
, Just 1
|
|
||||||
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
|
||||||
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
|
||||||
, False
|
|
||||||
)
|
|
||||||
, ( "missing goals"
|
|
||||||
, Just 0
|
|
||||||
, Just 1
|
|
||||||
, Nothing
|
|
||||||
, (0, 0, 0, 10, 11, 12, 20, 21, 22)
|
|
||||||
, (1, 2, 3, 30, 31, 32, 40, 41, 42)
|
|
||||||
, False
|
|
||||||
)
|
|
||||||
]
|
|
||||||
|
|
||||||
makePlayer :: IO Player
|
makePlayer :: IO Player
|
||||||
makePlayer = Player
|
makePlayer = Player
|
||||||
<$> makeNum
|
<$> makeNum
|
||||||
|
|
Loading…
Reference in New Issue
Block a user