Merge pull request #57 from mtlstats/batch-edit

Allow editing of player/goalie YTD/lifetime stats at once
This commit is contained in:
Jonathan Lamothe 2020-01-02 00:16:39 -05:00 committed by GitHub
commit ddb9394ab7
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
11 changed files with 296 additions and 866 deletions

View File

@ -1,164 +0,0 @@
{- |
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.EditGoalie
( editGoalieNumber
, editGoalieName
, editGoalieYtdGames
, editGoalieYtdMins
, editGoalieYtdGoals
, editGoalieYtdWins
, editGoalieYtdLosses
, editGoalieYtdTies
, editGoalieLtGames
, editGoalieLtMins
, editGoalieLtGoals
, editGoalieLtWins
, editGoalieLtLosses
, editGoalieLtTies
) where
import Control.Monad (void)
import Data.Maybe (fromMaybe)
import Lens.Micro ((^.), (&), (.~), (%~))
import Mtlstats.Types
import Mtlstats.Util
-- | Edits a goalie's number
editGoalieNumber
:: Int
-- ^ New goalie number
-> ProgState
-> ProgState
editGoalieNumber num = editGoalie (gNumber .~ num) EGMenu
-- | Edits a goalie's name
editGoalieName
:: String
-- ^ The new name
-> ProgState
-> ProgState
editGoalieName name = editGoalie (gName .~ name) EGMenu
-- | Edits a goalie's YTD games
editGoalieYtdGames
:: Int
-- ^ The number of games played
-> ProgState
-> ProgState
editGoalieYtdGames games = editGoalie (gYtd.gsGames .~ games) EGYtd
-- | Edits a goalie's YTD minutes
editGoalieYtdMins
:: Int
-- ^ The number of minutes played
-> ProgState
-> ProgState
editGoalieYtdMins mins = editGoalie (gYtd.gsMinsPlayed .~ mins) EGYtd
-- | Edits a goalie's YTD goals allowed
editGoalieYtdGoals
:: Int
-- ^ The number of goals
-> ProgState
-> ProgState
editGoalieYtdGoals goals = editGoalie (gYtd.gsGoalsAllowed .~ goals) EGYtd
-- | Edits a goalie's YTD wins
editGoalieYtdWins
:: Int
-- ^ The number of wins
-> ProgState
-> ProgState
editGoalieYtdWins wins = editGoalie (gYtd.gsWins .~ wins) EGYtd
-- | Edits a goalie's YTD losses
editGoalieYtdLosses
:: Int
-- ^ The number of losses
-> ProgState
-> ProgState
editGoalieYtdLosses losses = editGoalie (gYtd.gsLosses .~ losses) EGYtd
-- | Edits a goalie's YTD ties
editGoalieYtdTies
:: Int
-- ^ The number of ties
-> ProgState
-> ProgState
editGoalieYtdTies ties = editGoalie (gYtd.gsTies .~ ties) EGYtd
-- | Edits a goalie's lifetime games played
editGoalieLtGames
:: Int
-- ^ The number of games
-> ProgState
-> ProgState
editGoalieLtGames games = editGoalie (gLifetime.gsGames .~ games) EGLifetime
-- | Edits a goalie's lifetime minutes played
editGoalieLtMins
:: Int
-- ^ The number of minutes
-> ProgState
-> ProgState
editGoalieLtMins mins = editGoalie (gLifetime.gsMinsPlayed .~ mins) EGLifetime
-- | Edits a goalie's lifetime goals allowed
editGoalieLtGoals
:: Int
-- ^ The number of goals
-> ProgState
-> ProgState
editGoalieLtGoals goals = editGoalie (gLifetime.gsGoalsAllowed .~ goals) EGLifetime
-- | Edits a goalie's lifetime wins
editGoalieLtWins
:: Int
-- ^ The number of wins
-> ProgState
-> ProgState
editGoalieLtWins wins = editGoalie (gLifetime.gsWins .~ wins) EGLifetime
-- | Edits a goalie's lifetime losses
editGoalieLtLosses
:: Int
-- ^ The number of losses
-> ProgState
-> ProgState
editGoalieLtLosses losses = editGoalie (gLifetime.gsLosses .~ losses) EGLifetime
-- | Edits a goalie's lifetime ties
editGoalieLtTies
:: Int
-- ^ The number of ties
-> ProgState
-> ProgState
editGoalieLtTies ties = editGoalie (gLifetime.gsTies .~ ties) EGLifetime
editGoalie :: (Goalie -> Goalie) -> EditGoalieMode -> ProgState -> ProgState
editGoalie f mode s = fromMaybe s $ do
gid <- s^.progMode.editGoalieStateL.egsSelectedGoalie
void $ nth gid $ s^.database.dbGoalies
Just $ s
& database.dbGoalies %~ modifyNth gid f
& progMode.editGoalieStateL.egsMode .~ mode

View File

@ -51,17 +51,17 @@ editC = \case
EGName -> nameC EGName -> nameC
EGYtd -> ytdMenuC EGYtd -> ytdMenuC
EGLifetime -> lifetimeMenuC EGLifetime -> lifetimeMenuC
EGYtdGames -> ytdGamesC EGYtdGames b -> ytdGamesC b
EGYtdMins -> ytdMinsC EGYtdMins b -> ytdMinsC b
EGYtdGoals -> ytdGoalsC EGYtdGoals b -> ytdGoalsC b
EGYtdWins -> ytdWinsC EGYtdWins b -> ytdWinsC b
EGYtdLosses -> ytdLossesC EGYtdLosses b -> ytdLossesC b
EGYtdTies -> ytdTiesC EGYtdTies -> ytdTiesC
EGLtGames -> ltGamesC EGLtGames b -> ltGamesC b
EGLtMins -> ltMinsC EGLtMins b -> ltMinsC b
EGLtGoals -> ltGoalsC EGLtGoals b -> ltGoalsC b
EGLtWins -> ltWinsC EGLtWins b -> ltWinsC b
EGLtLosses -> ltLossesC EGLtLosses b -> ltLossesC b
EGLtTies -> ltTiesC EGLtTies -> ltTiesC
menuC :: Controller menuC :: Controller
@ -79,38 +79,38 @@ ytdMenuC = menuControllerWith header editGoalieYtdMenu
lifetimeMenuC :: Controller lifetimeMenuC :: Controller
lifetimeMenuC = menuControllerWith header editGoalieLtMenu lifetimeMenuC = menuControllerWith header editGoalieLtMenu
ytdGamesC :: Controller ytdGamesC :: Bool -> Controller
ytdGamesC = promptController editGoalieYtdGamesPrompt ytdGamesC = promptController . editGoalieYtdGamesPrompt
ytdMinsC :: Controller ytdMinsC :: Bool -> Controller
ytdMinsC = promptController editGoalieYtdMinsPrompt ytdMinsC = promptController . editGoalieYtdMinsPrompt
ytdGoalsC :: Controller ytdGoalsC :: Bool -> Controller
ytdGoalsC = promptController editGoalieYtdGoalsPrompt ytdGoalsC = promptController . editGoalieYtdGoalsPrompt
ytdWinsC :: Controller ytdWinsC :: Bool -> Controller
ytdWinsC = promptController editGoalieYtdWinsPrompt ytdWinsC = promptController . editGoalieYtdWinsPrompt
ytdLossesC :: Controller ytdLossesC :: Bool -> Controller
ytdLossesC = promptController editGoalieYtdLossesPrompt ytdLossesC = promptController . editGoalieYtdLossesPrompt
ytdTiesC :: Controller ytdTiesC :: Controller
ytdTiesC = promptController editGoalieYtdTiesPrompt ytdTiesC = promptController editGoalieYtdTiesPrompt
ltGamesC :: Controller ltGamesC :: Bool -> Controller
ltGamesC = promptController editGoalieLtGamesPrompt ltGamesC = promptController . editGoalieLtGamesPrompt
ltMinsC :: Controller ltMinsC :: Bool -> Controller
ltMinsC = promptController editGoalieLtMinsPrompt ltMinsC = promptController . editGoalieLtMinsPrompt
ltGoalsC :: Controller ltGoalsC :: Bool -> Controller
ltGoalsC = promptController editGoalieLtGoalsPrompt ltGoalsC = promptController . editGoalieLtGoalsPrompt
ltWinsC :: Controller ltWinsC :: Bool -> Controller
ltWinsC = promptController editGoalieLtWinsPrompt ltWinsC = promptController . editGoalieLtWinsPrompt
ltLossesC :: Controller ltLossesC :: Bool -> Controller
ltLossesC = promptController editGoalieLtLossesPrompt ltLossesC = promptController . editGoalieLtLossesPrompt
ltTiesC :: Controller ltTiesC :: Controller
ltTiesC = promptController editGoalieLtTiesPrompt ltTiesC = promptController editGoalieLtTiesPrompt

View File

@ -44,11 +44,11 @@ editPlayerC eps
EPPosition -> positionC EPPosition -> positionC
EPYtd -> ytdC EPYtd -> ytdC
EPLifetime -> lifetimeC EPLifetime -> lifetimeC
EPYtdGoals -> ytdGoalsC EPYtdGoals b -> ytdGoalsC b
EPYtdAssists -> ytdAssistsC EPYtdAssists b -> ytdAssistsC b
EPYtdPMin -> ytdPMinC EPYtdPMin -> ytdPMinC
EPLtGoals -> ltGoalsC EPLtGoals b -> ltGoalsC b
EPLtAssists -> ltAssistsC EPLtAssists b -> ltAssistsC b
EPLtPMin -> ltPMinC EPLtPMin -> ltPMinC
selectPlayerC :: Controller selectPlayerC :: Controller
@ -72,20 +72,20 @@ ytdC = menuControllerWith header editPlayerYtdMenu
lifetimeC :: Controller lifetimeC :: Controller
lifetimeC = menuControllerWith header editPlayerLtMenu lifetimeC = menuControllerWith header editPlayerLtMenu
ytdGoalsC :: Controller ytdGoalsC :: Bool -> Controller
ytdGoalsC = promptController editPlayerYtdGoalsPrompt ytdGoalsC = promptController . editPlayerYtdGoalsPrompt
ytdAssistsC :: Controller ytdAssistsC :: Bool -> Controller
ytdAssistsC = promptController editPlayerYtdAssistsPrompt ytdAssistsC = promptController . editPlayerYtdAssistsPrompt
ytdPMinC :: Controller ytdPMinC :: Controller
ytdPMinC = promptController editPlayerYtdPMinPrompt ytdPMinC = promptController editPlayerYtdPMinPrompt
ltGoalsC :: Controller ltGoalsC :: Bool -> Controller
ltGoalsC = promptController editPlayerLtGoalsPrompt ltGoalsC = promptController . editPlayerLtGoalsPrompt
ltAssistsC :: Controller ltAssistsC :: Bool -> Controller
ltAssistsC = promptController editPlayerLtAssistsPrompt ltAssistsC = promptController . editPlayerLtAssistsPrompt
ltPMinC :: Controller ltPMinC :: Controller
ltPMinC = promptController editPlayerLtPMinPrompt ltPMinC = promptController editPlayerLtPMinPrompt

View File

@ -51,12 +51,13 @@ editGoalieMenu = Menu "*** EDIT GOALTENDER ***" () $ map
editGoalieYtdMenu :: Menu () editGoalieYtdMenu :: Menu ()
editGoalieYtdMenu = editMenu "*** EDIT GOALTENDER YEAR-TO-DATE ***" editGoalieYtdMenu = editMenu "*** EDIT GOALTENDER YEAR-TO-DATE ***"
-- key, label, value -- key, label, value
[ ( '1', "Edit YTD games", EGYtdGames ) [ ( '1', "Edit all YTD stats", EGYtdGames True )
, ( '2', "Edit YTD minutes", EGYtdMins ) , ( '2', "Edit YTD games", EGYtdGames False )
, ( '3', "Edit YTD goals", EGYtdGoals ) , ( '3', "Edit YTD minutes", EGYtdMins False )
, ( '4', "Edit YTD wins", EGYtdWins ) , ( '4', "Edit YTD goals", EGYtdGoals False )
, ( '5', "Edit YTD losses", EGYtdLosses ) , ( '5', "Edit YTD wins", EGYtdWins False )
, ( '6', "Edit YTD ties", EGYtdTies ) , ( '6', "Edit YTD losses", EGYtdLosses False )
, ( '7', "Edit YTD ties", EGYtdTies )
, ( 'R', "Return to edit menu", EGMenu ) , ( 'R', "Return to edit menu", EGMenu )
] ]
@ -65,12 +66,13 @@ editGoalieLtMenu :: Menu ()
editGoalieLtMenu = editMenu editGoalieLtMenu = editMenu
"*** EDIT GOALTENDER LIFETIME ***" "*** EDIT GOALTENDER LIFETIME ***"
-- key, label, value -- key, label, value
[ ( '1', "Edit lifetime games", EGLtGames ) [ ( '1', "Edit all lifetime stats", EGLtGames True )
, ( '2', "Edit lifetime minutes", EGLtMins ) , ( '2', "Edit lifetime games", EGLtGames False )
, ( '3', "Edit lifetime goals", EGLtGoals ) , ( '3', "Edit lifetime minutes", EGLtMins False )
, ( '4', "Edit lifetime wins", EGLtWins ) , ( '4', "Edit lifetime goals", EGLtGoals False )
, ( '5', "Edit lifetime losses", EGLtLosses ) , ( '5', "Edit lifetime wins", EGLtWins False )
, ( '6', "Edit lifetime ties", EGLtTies ) , ( '6', "Edit lifetime losses", EGLtLosses False )
, ( '7', "Edit lifetime ties", EGLtTies )
, ( 'R', "Return to edit menu", EGMenu ) , ( 'R', "Return to edit menu", EGMenu )
] ]

View File

@ -53,9 +53,10 @@ editPlayerYtdMenu :: Menu ()
editPlayerYtdMenu = editMenu editPlayerYtdMenu = editMenu
"*** EDIT PLAYER YEAR-TO-DATE ***" "*** EDIT PLAYER YEAR-TO-DATE ***"
-- key, label, value -- key, label, value
[ ( '1', "Edit YTD goals", EPYtdGoals ) [ ( '1', "Edit all YTD stats", EPYtdGoals True )
, ( '2', "Edit YTD assists", EPYtdAssists ) , ( '2', "Edit YTD goals", EPYtdGoals False )
, ( '3', "Edit YTD penalty mins", EPYtdPMin ) , ( '3', "Edit YTD assists", EPYtdAssists False )
, ( '4', "Edit YTD penalty mins", EPYtdPMin )
, ( 'R', "Return to player edit menu", EPMenu ) , ( 'R', "Return to player edit menu", EPMenu )
] ]
@ -64,9 +65,10 @@ editPlayerLtMenu :: Menu ()
editPlayerLtMenu = editMenu editPlayerLtMenu = editMenu
"*** EDIT PLAYER LIFETIME ***" "*** EDIT PLAYER LIFETIME ***"
-- key, label, value -- key, label, value
[ ( '1', "Edit lifetime goals", EPLtGoals ) [ ( '1', "Edit all lifetime stats", EPLtGoals True )
, ( '2', "Edit lifetime assits", EPLtAssists ) , ( '2', "Edit lifetime goals", EPLtGoals False )
, ( '3', "Edit lifetime penalty mins", EPLtPMin ) , ( '3', "Edit lifetime assits", EPLtAssists False )
, ( '4', "Edit lifetime penalty mins", EPLtPMin )
, ( 'R', "Return to edit player menu", EPMenu ) , ( 'R', "Return to edit player menu", EPMenu )
] ]

View File

@ -31,6 +31,7 @@ module Mtlstats.Prompt (
ucStrPrompt, ucStrPrompt,
namePrompt, namePrompt,
numPrompt, numPrompt,
numPromptWithFallback,
selectPrompt, selectPrompt,
-- * Individual prompts -- * Individual prompts
playerNumPrompt, playerNumPrompt,
@ -47,7 +48,6 @@ import Control.Monad (when)
import Control.Monad.Extra (whenJust) import Control.Monad.Extra (whenJust)
import Control.Monad.Trans.State (gets, modify) import Control.Monad.Trans.State (gets, modify)
import Data.Char (isDigit, toUpper) import Data.Char (isDigit, toUpper)
import Data.Foldable (forM_)
import Lens.Micro ((^.), (&), (.~), (?~), (%~)) import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import Lens.Micro.Extras (view) import Lens.Micro.Extras (view)
import Text.Read (readMaybe) import Text.Read (readMaybe)
@ -145,12 +145,25 @@ numPrompt
-> (Int -> Action ()) -> (Int -> Action ())
-- ^ The callback function for the result -- ^ The callback function for the result
-> Prompt -> Prompt
numPrompt pStr act = Prompt numPrompt pStr = numPromptWithFallback pStr $ return ()
-- | Builds a numeric prompt with a fallback action
numPromptWithFallback
:: String
-- ^ The prompt string
-> Action ()
-- ^ The action to call on invalid (or blank) input
-> (Int -> Action ())
-- ^ The callback function for the result
-> Prompt
numPromptWithFallback pStr fallback act = Prompt
{ promptDrawer = drawSimplePrompt pStr { promptDrawer = drawSimplePrompt pStr
, promptProcessChar = \ch str -> if isDigit ch , promptProcessChar = \ch str -> if isDigit ch
then str ++ [ch] then str ++ [ch]
else str else str
, promptAction = \inStr -> forM_ (readMaybe inStr) act , promptAction = \inStr -> case readMaybe inStr of
Nothing -> fallback
Just n -> act n
, promptSpecialKey = const $ return () , promptSpecialKey = const $ return ()
} }

View File

@ -37,12 +37,13 @@ module Mtlstats.Prompt.EditGoalie
, editGoalieLtTiesPrompt , editGoalieLtTiesPrompt
) where ) where
import Control.Monad.Trans.State (modify) import Control.Monad.Extra (whenJustM)
import Lens.Micro ((.~)) import Control.Monad.Trans.State (gets, modify)
import Lens.Micro ((^.), (.~), (%~))
import Mtlstats.Actions.EditGoalie
import Mtlstats.Prompt import Mtlstats.Prompt
import Mtlstats.Types import Mtlstats.Types
import Mtlstats.Util
-- | Prompt to select a 'Goalie' for editing -- | Prompt to select a 'Goalie' for editing
goalieToEditPrompt :: Prompt goalieToEditPrompt :: Prompt
@ -51,70 +52,150 @@ goalieToEditPrompt = selectGoaliePrompt "Goalie to edit: " $
-- | Prompt to edit a goalie's number -- | Prompt to edit a goalie's number
editGoalieNumberPrompt :: Prompt editGoalieNumberPrompt :: Prompt
editGoalieNumberPrompt = numPrompt "Goalie number: " $ editGoalieNumberPrompt = editNum "Goalie number: " EGMenu
modify . editGoalieNumber (gNumber .~)
-- | Prompt to edit a goalie's name -- | Prompt to edit a goalie's name
editGoalieNamePrompt :: Prompt editGoalieNamePrompt :: Prompt
editGoalieNamePrompt = namePrompt "Goalie name: " $ editGoalieNamePrompt = namePrompt "Goalie name: " $ \name ->
modify . editGoalieName if null name
then goto EGMenu
else editGoalie EGMenu $ gName .~ name
-- | Prompt to edit a goalie's YTD games played -- | Prompt to edit a goalie's YTD games played
editGoalieYtdGamesPrompt :: Prompt editGoalieYtdGamesPrompt
editGoalieYtdGamesPrompt = numPrompt "Year-to-date games played: " $ :: Bool
modify . editGoalieYtdGames -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieYtdGamesPrompt batchMode =
editNum "Year-to-date games played: " mode
(gYtd.gsGames .~)
where
mode = if batchMode then EGYtdMins True else EGYtd
-- | Prompt to edit a goalie's YTD minutes played -- | Prompt to edit a goalie's YTD minutes played
editGoalieYtdMinsPrompt :: Prompt editGoalieYtdMinsPrompt
editGoalieYtdMinsPrompt = numPrompt "Year-to-date minutes played: " $ :: Bool
modify . editGoalieYtdMins -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieYtdMinsPrompt batchMode =
editNum "Year-to-date minutes played: " mode
(gYtd.gsMinsPlayed .~)
where
mode = if batchMode then EGYtdGoals True else EGYtd
-- | Prompt to edit a goalie's YTD goales allowed -- | Prompt to edit a goalie's YTD goales allowed
editGoalieYtdGoalsPrompt :: Prompt editGoalieYtdGoalsPrompt
editGoalieYtdGoalsPrompt = numPrompt "Year-to-date goals allowed: " $ :: Bool
modify . editGoalieYtdGoals -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieYtdGoalsPrompt batchMode =
editNum "Year-to-date goals allowed: " mode
(gYtd.gsGoalsAllowed .~)
where
mode = if batchMode then EGYtdWins True else EGYtd
-- | Prompt to edit a goalie's YTD wins -- | Prompt to edit a goalie's YTD wins
editGoalieYtdWinsPrompt :: Prompt editGoalieYtdWinsPrompt
editGoalieYtdWinsPrompt = numPrompt "Year-to-date wins: " $ :: Bool
modify . editGoalieYtdWins -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieYtdWinsPrompt batchMode =
editNum "Year-to-date wins: " mode
(gYtd.gsWins .~)
where
mode = if batchMode then EGYtdLosses True else EGYtd
-- | Prompt to edit a goalie's YTD losses -- | Prompt to edit a goalie's YTD losses
editGoalieYtdLossesPrompt :: Prompt editGoalieYtdLossesPrompt
editGoalieYtdLossesPrompt = numPrompt "Year-to-date losses: " $ :: Bool
modify . editGoalieYtdLosses -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieYtdLossesPrompt batchMode =
editNum "Year-to-date losses: " mode
(gYtd.gsLosses .~)
where
mode = if batchMode then EGYtdTies else EGYtd
-- | Prompt to edit a goalie's YTD ties -- | Prompt to edit a goalie's YTD ties
editGoalieYtdTiesPrompt :: Prompt editGoalieYtdTiesPrompt :: Prompt
editGoalieYtdTiesPrompt = numPrompt "Year-to-date ties: " $ editGoalieYtdTiesPrompt = editNum "Year-to-date ties: " EGYtd
modify . editGoalieYtdTies (gYtd.gsTies .~)
-- | Prompt to edit a goalie's lifetime games played -- | Prompt to edit a goalie's lifetime games played
editGoalieLtGamesPrompt :: Prompt editGoalieLtGamesPrompt
editGoalieLtGamesPrompt = numPrompt "Lifetime games played: " $ :: Bool
modify . editGoalieLtGames -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieLtGamesPrompt batchMode =
editNum "Lifetime games played: " mode
(gLifetime.gsGames .~)
where
mode = if batchMode then EGLtMins True else EGLifetime
-- | Prompt to edit a goalie's lifetime minutes played -- | Prompt to edit a goalie's lifetime minutes played
editGoalieLtMinsPrompt :: Prompt editGoalieLtMinsPrompt
editGoalieLtMinsPrompt = numPrompt "Lifetime minutes played: " $ :: Bool
modify . editGoalieLtMins -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieLtMinsPrompt batchMode =
editNum "Lifetime minutes played: " mode
(gLifetime.gsMinsPlayed .~)
where
mode = if batchMode then EGLtGoals True else EGLifetime
-- | Prompt to edit a goalie's lifetime goals allowed -- | Prompt to edit a goalie's lifetime goals allowed
editGoalieLtGoalsPrompt :: Prompt editGoalieLtGoalsPrompt
editGoalieLtGoalsPrompt = numPrompt "Lifetime goals allowed: " $ :: Bool
modify . editGoalieLtGoals -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieLtGoalsPrompt batchMode =
editNum "Lifetime goals allowed: " mode
(gLifetime.gsGoalsAllowed .~)
where
mode = if batchMode then EGLtWins True else EGLifetime
-- | Prompt to edit a goalie's lifetime wins -- | Prompt to edit a goalie's lifetime wins
editGoalieLtWinsPrompt :: Prompt editGoalieLtWinsPrompt
editGoalieLtWinsPrompt = numPrompt "Lifetime wins: " $ :: Bool
modify . editGoalieLtWins -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieLtWinsPrompt batchMode =
editNum "Lifetime wins: " mode
(gLifetime.gsWins .~)
where
mode = if batchMode then EGLtLosses True else EGLifetime
-- | Prompt to edit a goalie's lifetime losses -- | Prompt to edit a goalie's lifetime losses
editGoalieLtLossesPrompt :: Prompt editGoalieLtLossesPrompt
editGoalieLtLossesPrompt = numPrompt "Lifetime losses: " $ :: Bool
modify . editGoalieLtLosses -- ^ Indicates whether or not we're in batch mode
-> Prompt
editGoalieLtLossesPrompt batchMode =
editNum "Lifetime losses: " mode
(gLifetime.gsLosses .~)
where
mode = if batchMode then EGLtTies else EGLifetime
-- | Prompt to edit a goalie's lifetime ties -- | Prompt to edit a goalie's lifetime ties
editGoalieLtTiesPrompt :: Prompt editGoalieLtTiesPrompt :: Prompt
editGoalieLtTiesPrompt = numPrompt "Lifetime ties: " $ editGoalieLtTiesPrompt = editNum "Lifetime ties: " EGLifetime
modify . editGoalieLtTies (gLifetime.gsTies .~)
editNum
:: String
-> EditGoalieMode
-> (Int -> Goalie -> Goalie)
-> Prompt
editNum pStr mode f = numPromptWithFallback pStr
(goto mode)
(editGoalie mode . f)
editGoalie :: EditGoalieMode -> (Goalie -> Goalie) -> Action ()
editGoalie mode f =
whenJustM (gets (^.progMode.editGoalieStateL.egsSelectedGoalie)) $ \gid -> do
modify $ database.dbGoalies %~ modifyNth gid f
goto mode
goto :: EditGoalieMode -> Action ()
goto = modify . (progMode.editGoalieStateL.egsMode .~)

View File

@ -41,52 +41,87 @@ import Mtlstats.Util
-- | Prompt to edit a player's number -- | Prompt to edit a player's number
editPlayerNumPrompt :: Prompt editPlayerNumPrompt :: Prompt
editPlayerNumPrompt = numPrompt "Player number: " $ editPlayerNumPrompt = editNum "Player number: " EPMenu
editPlayer EPMenu . (pNumber .~) (pNumber .~)
-- | Prompt to edit a player's name -- | Prompt to edit a player's name
editPlayerNamePrompt :: Prompt editPlayerNamePrompt :: Prompt
editPlayerNamePrompt = namePrompt "Player name: " $ editPlayerNamePrompt = namePrompt "Player name: " $ \name ->
editPlayer EPMenu . (pName .~) if null name
then goto EPMenu
else editPlayer EPMenu $ pName .~ name
-- | Prompt to edit a player's position -- | Prompt to edit a player's position
editPlayerPosPrompt :: Prompt editPlayerPosPrompt :: Prompt
editPlayerPosPrompt = ucStrPrompt "Player position: " $ editPlayerPosPrompt = ucStrPrompt "Player position: " $ \pos ->
editPlayer EPMenu . (pPosition .~) if null pos
then goto EPMenu
else editPlayer EPMenu $ pPosition .~ pos
-- | Prompt to edit a player's year-to-date goals -- | Prompt to edit a player's year-to-date goals
editPlayerYtdGoalsPrompt :: Prompt editPlayerYtdGoalsPrompt
editPlayerYtdGoalsPrompt = numPrompt "Year-to-date goals: " $ :: Bool
editPlayer EPYtd . (pYtd.psGoals .~) -- ^ Indicates wheter or not we're editing in batch mode
-> Prompt
editPlayerYtdGoalsPrompt batchMode = editNum "Year-to-date goals: " mode
(pYtd.psGoals .~)
where
mode = if batchMode then EPYtdAssists True else EPYtd
-- | Prompt to edit a player's year-to-date assists -- | Prompt to edit a player's year-to-date assists
editPlayerYtdAssistsPrompt :: Prompt editPlayerYtdAssistsPrompt
editPlayerYtdAssistsPrompt = numPrompt "Year-to-date assists: " $ :: Bool
editPlayer EPYtd . (pYtd.psAssists .~) -- ^ Indicates wheter or not we're editing in batch mode
-> Prompt
editPlayerYtdAssistsPrompt batchMode = editNum "Year-to-date assists: " mode
(pYtd.psAssists .~)
where
mode = if batchMode then EPYtdPMin else EPYtd
-- | Prompt to edit a player's year-to-date penalty minutes -- | Prompt to edit a player's year-to-date penalty minutes
editPlayerYtdPMinPrompt :: Prompt editPlayerYtdPMinPrompt :: Prompt
editPlayerYtdPMinPrompt = numPrompt "Year-to-date penalty minutes: " $ editPlayerYtdPMinPrompt = editNum "Year-to-date penalty minutes: " EPYtd
editPlayer EPYtd . (pYtd.psPMin .~) (pYtd.psPMin .~)
-- | Prompt to edit a player's lifetime goals -- | Prompt to edit a player's lifetime goals
editPlayerLtGoalsPrompt :: Prompt editPlayerLtGoalsPrompt
editPlayerLtGoalsPrompt = numPrompt "Lifetime goals: " $ :: Bool
editPlayer EPLifetime . (pLifetime.psGoals .~) -- ^ Indicates wheter or not we're editing in batch mode
-> Prompt
editPlayerLtGoalsPrompt batchMode = editNum "Lifetime goals: " mode
(pLifetime.psGoals .~)
where
mode = if batchMode then EPLtAssists True else EPLifetime
-- | Prompt to edit a player's lifetime assists -- | Prompt to edit a player's lifetime assists
editPlayerLtAssistsPrompt :: Prompt editPlayerLtAssistsPrompt
editPlayerLtAssistsPrompt = numPrompt "Lifetime assists: " $ :: Bool
editPlayer EPLifetime . (pLifetime.psAssists .~) -- ^ Indicates wheter or not we're editing in batch mode
-> Prompt
editPlayerLtAssistsPrompt batchMode = editNum "Lifetime assists: " mode
(pLifetime.psAssists .~)
where
mode = if batchMode then EPLtPMin else EPLifetime
-- | Prompt to edit a player's lifetime penalty minutes -- | Prompt to edit a player's lifetime penalty minutes
editPlayerLtPMinPrompt :: Prompt editPlayerLtPMinPrompt :: Prompt
editPlayerLtPMinPrompt = numPrompt "Lifetime penalty minutes: " $ editPlayerLtPMinPrompt = editNum "Lifetime penalty minutes: " EPLifetime
editPlayer EPLifetime . (pLifetime.psPMin .~) (pLifetime.psPMin .~)
editNum
:: String
-> EditPlayerMode
-> (Int -> Player -> Player)
-> Prompt
editNum pStr mode f = numPromptWithFallback pStr
(goto mode)
(editPlayer mode . f)
editPlayer :: EditPlayerMode -> (Player -> Player) -> Action () editPlayer :: EditPlayerMode -> (Player -> Player) -> Action ()
editPlayer mode f = editPlayer mode f =
whenJustM (gets (^.progMode.editPlayerStateL.epsSelectedPlayer)) $ \pid -> whenJustM (gets (^.progMode.editPlayerStateL.epsSelectedPlayer)) $ \pid -> do
modify modify $ database.dbPlayers %~ modifyNth pid f
$ (database.dbPlayers %~ modifyNth pid f) goto mode
. (progMode.editPlayerStateL.epsMode .~ mode)
goto :: EditPlayerMode -> Action ()
goto = modify . (progMode.editPlayerStateL.epsMode .~)

View File

@ -347,11 +347,11 @@ data EditPlayerMode
| EPPosition | EPPosition
| EPYtd | EPYtd
| EPLifetime | EPLifetime
| EPYtdGoals | EPYtdGoals Bool
| EPYtdAssists | EPYtdAssists Bool
| EPYtdPMin | EPYtdPMin
| EPLtGoals | EPLtGoals Bool
| EPLtAssists | EPLtAssists Bool
| EPLtPMin | EPLtPMin
deriving (Eq, Show) deriving (Eq, Show)
@ -369,17 +369,17 @@ data EditGoalieMode
| EGName | EGName
| EGYtd | EGYtd
| EGLifetime | EGLifetime
| EGYtdGames | EGYtdGames Bool
| EGYtdMins | EGYtdMins Bool
| EGYtdGoals | EGYtdGoals Bool
| EGYtdWins | EGYtdWins Bool
| EGYtdLosses | EGYtdLosses Bool
| EGYtdTies | EGYtdTies
| EGLtGames | EGLtGames Bool
| EGLtMins | EGLtMins Bool
| EGLtGoals | EGLtGoals Bool
| EGLtWins | EGLtWins Bool
| EGLtLosses | EGLtLosses Bool
| EGLtTies | EGLtTies
deriving (Eq, Show) deriving (Eq, Show)

View File

@ -1,537 +0,0 @@
{-
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.EditGoalieSpec (spec) where
import Data.Maybe (fromJust)
import Lens.Micro ((^.), (&), (.~))
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Actions.EditGoalie
import Mtlstats.Types
import Mtlstats.Util
spec :: Spec
spec = describe "EditGoalie" $ do
editGoalieNumberSpec
editGoalieNameSpec
editGoalieYtdGamesSpec
editGoalieYtdMinsSpec
editGoalieYtdGoalsSpec
editGoalieYtdWinsSpec
editGoalieYtdLossesSpec
editGoalieYtdTiesSpec
editGoalieLtGamesSpec
editGoalieLtMinsSpec
editGoalieLtGoalsSpec
editGoalieLtWinsSpec
editGoalieLtLossesSpec
editGoalieLtTiesSpec
editGoalieNumberSpec :: Spec
editGoalieNumberSpec = describe "editGoalieNumber" $ editTest
(editGoalieNumber 5)
EGNumber
(uncurry newGoalie)
[ ( "set Joe"
, Just 0
, (5, "Joe")
, (3, "Bob")
, EGMenu
)
, ( "set Bob"
, Just 1
, (2, "Joe")
, (5, "Bob")
, EGMenu
)
, ( "out of bounds"
, Just 2
, (2, "Joe")
, (3, "Bob")
, EGNumber
)
, ( "no goalie selected"
, Nothing
, (2, "Joe")
, (3, "Bob")
, EGNumber
)
]
editGoalieNameSpec :: Spec
editGoalieNameSpec = describe "editGoalieName" $ editTest
(editGoalieName "foo")
EGName
(uncurry newGoalie)
[ ( "set Joe"
, Just 0
, ( 2, "foo" )
, ( 3, "Bob" )
, EGMenu
)
, ( "set Bob"
, Just 1
, ( 2, "Joe" )
, ( 3, "foo" )
, EGMenu
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe" )
, ( 3, "Bob" )
, EGName
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe" )
, ( 3, "Bob" )
, EGName
)
]
editGoalieYtdGamesSpec :: Spec
editGoalieYtdGamesSpec = describe "editGoalieYtdGames" $ editTest
(editGoalieYtdGames 1)
EGYtdGames
(\(num, name, games) -> newGoalie num name & gYtd.gsGames .~ games)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdGames
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdGames
)
]
editGoalieYtdMinsSpec :: Spec
editGoalieYtdMinsSpec = describe "editGoalieYtdMins" $ editTest
(editGoalieYtdMins 1)
EGYtdMins
(\(num, name, mins) -> newGoalie num name & gYtd.gsMinsPlayed .~ mins)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, (2, "Joe", 0 )
, (3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdMins
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdMins
)
]
editGoalieYtdGoalsSpec :: Spec
editGoalieYtdGoalsSpec = describe "editGoalieYtdGoals" $ editTest
(editGoalieYtdGoals 1)
EGYtdGoals
(\(num, name, goals) -> newGoalie num name & gYtd.gsGoalsAllowed .~ goals)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdGoals
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdGoals
)
]
editGoalieYtdWinsSpec :: Spec
editGoalieYtdWinsSpec = describe "editGoalieYtdWins" $ editTest
(editGoalieYtdWins 1)
EGYtdWins
(\(num, name, wins) -> newGoalie num name & gYtd.gsWins .~ wins)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdWins
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdWins
)
]
editGoalieYtdLossesSpec :: Spec
editGoalieYtdLossesSpec = describe "editGoalieYtdLosses" $ editTest
(editGoalieYtdLosses 1)
EGYtdLosses
(\(num, name, losses) -> newGoalie num name & gYtd.gsLosses .~ losses)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdLosses
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdLosses
)
]
editGoalieYtdTiesSpec :: Spec
editGoalieYtdTiesSpec = describe "editGoalieYtdTies" $ editTest
(editGoalieYtdTies 1)
EGYtdTies
(\(num, name, ties) -> newGoalie num name & gYtd.gsTies .~ ties)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGYtd
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGYtd
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdTies
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGYtdTies
)
]
editGoalieLtGamesSpec :: Spec
editGoalieLtGamesSpec = describe "editGoalieLtGames" $ editTest
(editGoalieLtGames 1)
EGLtGames
(\(num, name, games) -> newGoalie num name & gLifetime.gsGames .~ games)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtGames
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtGames
)
]
editGoalieLtMinsSpec :: Spec
editGoalieLtMinsSpec = describe "editGoalieLtMins" $ editTest
(editGoalieLtMins 1)
EGLtMins
(\(num, name, mins) -> newGoalie num name & gLifetime.gsMinsPlayed .~ mins)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtMins
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtMins
)
]
editGoalieLtGoalsSpec :: Spec
editGoalieLtGoalsSpec = describe "editGoalieLtGoals" $ editTest
(editGoalieLtGoals 1)
EGLtGoals
(\(num, name, goals) -> newGoalie num name & gLifetime.gsGoalsAllowed .~ goals)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtGoals
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtGoals
)
]
editGoalieLtWinsSpec :: Spec
editGoalieLtWinsSpec = describe "editGoalieLtWins" $ editTest
(editGoalieLtWins 1)
EGLtWins
(\(num, name, wins) -> newGoalie num name & gLifetime.gsWins .~ wins)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtWins
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtWins
)
]
editGoalieLtLossesSpec :: Spec
editGoalieLtLossesSpec = describe "editGoalieLtLosses" $ editTest
(editGoalieLtLosses 1)
EGLtLosses
(\(num, name, losses) -> newGoalie num name & gLifetime.gsLosses .~ losses)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtLosses
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtLosses
)
]
editGoalieLtTiesSpec :: Spec
editGoalieLtTiesSpec = describe "editGoalieLtTies" $ editTest
(editGoalieLtTies 1)
EGLtTies
(\(num, name, ties) -> newGoalie num name & gLifetime.gsTies .~ ties)
[ ( "set Joe"
, Just 0
, ( 2, "Joe", 1 )
, ( 3, "Bob", 0 )
, EGLifetime
)
, ( "set Bob"
, Just 1
, ( 2, "Joe", 0 )
, ( 3, "Bob", 1 )
, EGLifetime
)
, ( "out of bounds"
, Just 2
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtTies
)
, ( "no goalie selected"
, Nothing
, ( 2, "Joe", 0 )
, ( 3, "Bob", 0 )
, EGLtTies
)
]
editTest
:: (ProgState -> ProgState)
-> EditGoalieMode
-> (a -> Goalie)
-> [(String, Maybe Int, a, a, EditGoalieMode)]
-> Spec
editTest func setMode mkGoalie params = do
mapM_
(\(setLabel, setGid, joeData, bobData, expectMode) -> context setLabel $ do
let
egs = newEditGoalieState
& egsSelectedGoalie .~ setGid
& egsMode .~ setMode
ps = func $ progState $ EditGoalie egs
mapM_
(\(chkLabel, chkGid, goalieData) -> context chkLabel $ let
actual = fromJust $ nth chkGid $ ps^.database.dbGoalies
expected = mkGoalie goalieData
in it ("should be " ++ show expected) $
actual `shouldBe` expected)
-- label, goalie ID, goalie data
[ ( "check Joe", 0, joeData )
, ( "check Bob", 1, bobData )
]
context "check mode" $
it ("should be " ++ show expectMode) $
ps^.progMode.editGoalieStateL.egsMode `shouldBe` expectMode)
params
context "wrong progMode" $ do
let ps = func $ progState MainMenu
it "should not change the database" $
ps^.database `shouldBe` db
it "should not change the progMode" $
show (ps^.progMode) `shouldBe` "MainMenu"
joe :: Goalie
joe = newGoalie 2 "Joe"
bob :: Goalie
bob = newGoalie 3 "Bob"
db :: Database
db = newDatabase & dbGoalies .~ [joe, bob]
progState :: ProgMode -> ProgState
progState mode = newProgState
& progMode .~ mode
& database .~ db

View File

@ -38,7 +38,6 @@ import Test.Hspec
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Types import Mtlstats.Types
import qualified Actions.EditGoalieSpec as EditGoalie
import qualified Actions.NewGameSpec as NewGame import qualified Actions.NewGameSpec as NewGame
import qualified TypesSpec as TS import qualified TypesSpec as TS
@ -63,7 +62,6 @@ spec = describe "Mtlstats.Actions" $ do
scrollUpSpec scrollUpSpec
scrollDownSpec scrollDownSpec
NewGame.spec NewGame.spec
EditGoalie.spec
startNewSeasonSpec :: Spec startNewSeasonSpec :: Spec
startNewSeasonSpec = describe "startNewSeason" $ do startNewSeasonSpec = describe "startNewSeason" $ do