Merge pull request #36 from mtlstats/goalie-edit
implemented goalie editing
This commit is contained in:
commit
b830947d6c
|
@ -2,6 +2,7 @@
|
||||||
|
|
||||||
## current
|
## current
|
||||||
- Generate lifetime statistics report
|
- Generate lifetime statistics report
|
||||||
|
- Implemented goalie editing
|
||||||
|
|
||||||
## 0.5.0
|
## 0.5.0
|
||||||
|
|
||||||
|
|
|
@ -30,6 +30,7 @@ module Mtlstats.Actions
|
||||||
, createPlayer
|
, createPlayer
|
||||||
, createGoalie
|
, createGoalie
|
||||||
, editPlayer
|
, editPlayer
|
||||||
|
, editGoalie
|
||||||
, addPlayer
|
, addPlayer
|
||||||
, addGoalie
|
, addGoalie
|
||||||
, resetCreatePlayerState
|
, resetCreatePlayerState
|
||||||
|
@ -93,6 +94,10 @@ createGoalie = let
|
||||||
editPlayer :: ProgState -> ProgState
|
editPlayer :: ProgState -> ProgState
|
||||||
editPlayer = progMode .~ EditPlayer newEditPlayerState
|
editPlayer = progMode .~ EditPlayer newEditPlayerState
|
||||||
|
|
||||||
|
-- | Starts the 'Goalie' editing process
|
||||||
|
editGoalie :: ProgState -> ProgState
|
||||||
|
editGoalie = progMode .~ EditGoalie newEditGoalieState
|
||||||
|
|
||||||
-- | Adds the entered player to the roster
|
-- | Adds the entered player to the roster
|
||||||
addPlayer :: ProgState -> ProgState
|
addPlayer :: ProgState -> ProgState
|
||||||
addPlayer s = fromMaybe s $ do
|
addPlayer s = fromMaybe s $ do
|
||||||
|
|
|
@ -0,0 +1,164 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
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
|
|
@ -29,6 +29,7 @@ import Lens.Micro.Extras (view)
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
import Mtlstats.Actions
|
import Mtlstats.Actions
|
||||||
|
import Mtlstats.Control.EditGoalie
|
||||||
import Mtlstats.Control.EditPlayer
|
import Mtlstats.Control.EditPlayer
|
||||||
import Mtlstats.Control.NewGame
|
import Mtlstats.Control.NewGame
|
||||||
import Mtlstats.Handlers
|
import Mtlstats.Handlers
|
||||||
|
@ -53,6 +54,7 @@ dispatch s = case s^.progMode of
|
||||||
| null $ cgs^.cgsName -> getGoalieNameC
|
| null $ cgs^.cgsName -> getGoalieNameC
|
||||||
| otherwise -> confirmCreateGoalieC
|
| otherwise -> confirmCreateGoalieC
|
||||||
EditPlayer eps -> editPlayerC eps
|
EditPlayer eps -> editPlayerC eps
|
||||||
|
EditGoalie egs -> editGoalieC egs
|
||||||
|
|
||||||
mainMenuC :: Controller
|
mainMenuC :: Controller
|
||||||
mainMenuC = Controller
|
mainMenuC = Controller
|
||||||
|
|
|
@ -0,0 +1,137 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
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.Control.EditGoalie (editGoalieC) where
|
||||||
|
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import Lens.Micro ((^.))
|
||||||
|
import UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Menu
|
||||||
|
import Mtlstats.Menu.EditGoalie
|
||||||
|
import Mtlstats.Prompt
|
||||||
|
import Mtlstats.Prompt.EditGoalie
|
||||||
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
-- | Controller/dispatcher for editing a 'Goalie'
|
||||||
|
editGoalieC :: EditGoalieState -> Controller
|
||||||
|
editGoalieC egs
|
||||||
|
| null $ egs^.egsSelectedGoalie = selectC
|
||||||
|
| otherwise = editC $ egs^.egsMode
|
||||||
|
|
||||||
|
selectC :: Controller
|
||||||
|
selectC = promptController goalieToEditPrompt
|
||||||
|
|
||||||
|
editC :: EditGoalieMode -> Controller
|
||||||
|
editC = \case
|
||||||
|
EGMenu -> menuC
|
||||||
|
EGNumber -> numberC
|
||||||
|
EGName -> nameC
|
||||||
|
EGYtd -> ytdMenuC
|
||||||
|
EGLifetime -> lifetimeMenuC
|
||||||
|
EGYtdGames -> ytdGamesC
|
||||||
|
EGYtdMins -> ytdMinsC
|
||||||
|
EGYtdGoals -> ytdGoalsC
|
||||||
|
EGYtdWins -> ytdWinsC
|
||||||
|
EGYtdLosses -> ytdLossesC
|
||||||
|
EGYtdTies -> ytdTiesC
|
||||||
|
EGLtGames -> ltGamesC
|
||||||
|
EGLtMins -> ltMinsC
|
||||||
|
EGLtGoals -> ltGoalsC
|
||||||
|
EGLtWins -> ltWinsC
|
||||||
|
EGLtLosses -> ltLossesC
|
||||||
|
EGLtTies -> ltTiesC
|
||||||
|
|
||||||
|
menuC :: Controller
|
||||||
|
menuC = menuControllerWith header editGoalieMenu
|
||||||
|
|
||||||
|
numberC :: Controller
|
||||||
|
numberC = promptController editGoalieNumberPrompt
|
||||||
|
|
||||||
|
nameC :: Controller
|
||||||
|
nameC = promptController editGoalieNamePrompt
|
||||||
|
|
||||||
|
ytdMenuC :: Controller
|
||||||
|
ytdMenuC = menuControllerWith header editGoalieYtdMenu
|
||||||
|
|
||||||
|
lifetimeMenuC :: Controller
|
||||||
|
lifetimeMenuC = menuControllerWith header editGoalieLtMenu
|
||||||
|
|
||||||
|
ytdGamesC :: Controller
|
||||||
|
ytdGamesC = promptController editGoalieYtdGamesPrompt
|
||||||
|
|
||||||
|
ytdMinsC :: Controller
|
||||||
|
ytdMinsC = promptController editGoalieYtdMinsPrompt
|
||||||
|
|
||||||
|
ytdGoalsC :: Controller
|
||||||
|
ytdGoalsC = promptController editGoalieYtdGoalsPrompt
|
||||||
|
|
||||||
|
ytdWinsC :: Controller
|
||||||
|
ytdWinsC = promptController editGoalieYtdWinsPrompt
|
||||||
|
|
||||||
|
ytdLossesC :: Controller
|
||||||
|
ytdLossesC = promptController editGoalieYtdLossesPrompt
|
||||||
|
|
||||||
|
ytdTiesC :: Controller
|
||||||
|
ytdTiesC = promptController editGoalieYtdTiesPrompt
|
||||||
|
|
||||||
|
ltGamesC :: Controller
|
||||||
|
ltGamesC = promptController editGoalieLtGamesPrompt
|
||||||
|
|
||||||
|
ltMinsC :: Controller
|
||||||
|
ltMinsC = promptController editGoalieLtMinsPrompt
|
||||||
|
|
||||||
|
ltGoalsC :: Controller
|
||||||
|
ltGoalsC = promptController editGoalieLtGoalsPrompt
|
||||||
|
|
||||||
|
ltWinsC :: Controller
|
||||||
|
ltWinsC = promptController editGoalieLtWinsPrompt
|
||||||
|
|
||||||
|
ltLossesC :: Controller
|
||||||
|
ltLossesC = promptController editGoalieLtLossesPrompt
|
||||||
|
|
||||||
|
ltTiesC :: Controller
|
||||||
|
ltTiesC = promptController editGoalieLtTiesPrompt
|
||||||
|
|
||||||
|
header :: ProgState -> C.Update ()
|
||||||
|
header s = C.drawString $ fromMaybe "" $ do
|
||||||
|
gid <- s^.progMode.editGoalieStateL.egsSelectedGoalie
|
||||||
|
g <- nth gid $ s^.database.dbGoalies
|
||||||
|
Just $ unlines
|
||||||
|
[ " Goalie number: " ++ show (g^.gNumber)
|
||||||
|
, " Goalie name: " ++ g^.gName
|
||||||
|
, " YTD games played: " ++ show (g^.gYtd.gsGames)
|
||||||
|
, " YTD mins played: " ++ show (g^.gYtd.gsMinsPlayed)
|
||||||
|
, " YTD goals allowed: " ++ show (g^.gYtd.gsGoalsAllowed)
|
||||||
|
, " YTD wins: " ++ show (g^.gYtd.gsWins)
|
||||||
|
, " YTD losses: " ++ show (g^.gYtd.gsLosses)
|
||||||
|
, " YTD ties: " ++ show (g^.gYtd.gsTies)
|
||||||
|
, " Lifetime games played: " ++ show (g^.gLifetime.gsGames)
|
||||||
|
, " Lifetime mins played: " ++ show (g^.gLifetime.gsMinsPlayed)
|
||||||
|
, "Lifetime goals allowed: " ++ show (g^.gLifetime.gsGoalsAllowed)
|
||||||
|
, " Lifetime wins: " ++ show (g^.gLifetime.gsWins)
|
||||||
|
, " Lifetime losses: " ++ show (g^.gLifetime.gsLosses)
|
||||||
|
, " Lifetime ties: " ++ show (g^.gLifetime.gsTies)
|
||||||
|
, ""
|
||||||
|
]
|
|
@ -22,6 +22,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
module Mtlstats.Menu (
|
module Mtlstats.Menu (
|
||||||
-- * Menu Functions
|
-- * Menu Functions
|
||||||
menuController,
|
menuController,
|
||||||
|
menuControllerWith,
|
||||||
drawMenu,
|
drawMenu,
|
||||||
menuHandler,
|
menuHandler,
|
||||||
-- * Menus
|
-- * Menus
|
||||||
|
@ -57,8 +58,20 @@ import Mtlstats.Util
|
||||||
|
|
||||||
-- | Generates a simple 'Controller' for a Menu
|
-- | Generates a simple 'Controller' for a Menu
|
||||||
menuController :: Menu () -> Controller
|
menuController :: Menu () -> Controller
|
||||||
menuController menu = Controller
|
menuController = menuControllerWith $ const $ return ()
|
||||||
{ drawController = const $ drawMenu menu
|
|
||||||
|
-- | Generate a simple 'Controller' for a 'Menu' with a header
|
||||||
|
menuControllerWith
|
||||||
|
:: (ProgState -> C.Update ())
|
||||||
|
-- ^ Generates the header
|
||||||
|
-> Menu ()
|
||||||
|
-- ^ The menu
|
||||||
|
-> Controller
|
||||||
|
-- ^ The resulting controller
|
||||||
|
menuControllerWith header menu = Controller
|
||||||
|
{ drawController = \s -> do
|
||||||
|
header s
|
||||||
|
drawMenu menu
|
||||||
, handleController = \e -> do
|
, handleController = \e -> do
|
||||||
menuHandler menu e
|
menuHandler menu e
|
||||||
return True
|
return True
|
||||||
|
@ -91,7 +104,9 @@ mainMenu = Menu "*** MAIN MENU ***" True
|
||||||
modify createGoalie >> return True
|
modify createGoalie >> return True
|
||||||
, MenuItem '5' "Edit Player" $
|
, MenuItem '5' "Edit Player" $
|
||||||
modify editPlayer >> return True
|
modify editPlayer >> return True
|
||||||
, MenuItem '6' "Exit" $ do
|
, MenuItem '6' "Edit Goalie" $
|
||||||
|
modify editGoalie >> return True
|
||||||
|
, MenuItem 'X' "Exit" $ do
|
||||||
db <- gets $ view database
|
db <- gets $ view database
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
dir <- getAppUserDataDirectory appName
|
dir <- getAppUserDataDirectory appName
|
||||||
|
|
|
@ -0,0 +1,80 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
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.Menu.EditGoalie
|
||||||
|
( editGoalieMenu
|
||||||
|
, editGoalieYtdMenu
|
||||||
|
, editGoalieLtMenu
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (modify)
|
||||||
|
import Data.Maybe (maybe)
|
||||||
|
import Lens.Micro ((.~))
|
||||||
|
|
||||||
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Types.Menu
|
||||||
|
|
||||||
|
-- | The 'Goalie' edit menu
|
||||||
|
editGoalieMenu :: Menu ()
|
||||||
|
editGoalieMenu = Menu "*** EDIT GOALTENDER ***" () $ map
|
||||||
|
(\(key, label, val) -> MenuItem key label $ modify $ maybe
|
||||||
|
(progMode .~ MainMenu)
|
||||||
|
(progMode.editGoalieStateL.egsMode .~)
|
||||||
|
val)
|
||||||
|
-- key, label, value
|
||||||
|
[ ( '1', "Edit number", Just EGNumber )
|
||||||
|
, ( '2', "Edit name", Just EGName )
|
||||||
|
, ( '3', "Edit YTD stats", Just EGYtd )
|
||||||
|
, ( '4', "Edit Lifetime stats", Just EGLifetime )
|
||||||
|
, ( 'R', "Return to Main Menu", Nothing )
|
||||||
|
]
|
||||||
|
|
||||||
|
-- | The 'Goalie' YTD edit menu
|
||||||
|
editGoalieYtdMenu :: Menu ()
|
||||||
|
editGoalieYtdMenu = editMenu "*** EDIT GOALTENDER YEAR-TO-DATE ***"
|
||||||
|
-- key, label, value
|
||||||
|
[ ( '1', "Edit YTD games", EGYtdGames )
|
||||||
|
, ( '2', "Edit YTD minutes", EGYtdMins )
|
||||||
|
, ( '3', "Edit YTD goals", EGYtdGoals )
|
||||||
|
, ( '4', "Edit YTD wins", EGYtdWins )
|
||||||
|
, ( '5', "Edit YTD losses", EGYtdLosses )
|
||||||
|
, ( '6', "Edit YTD ties", EGYtdTies )
|
||||||
|
, ( 'R', "Return to edit menu", EGMenu )
|
||||||
|
]
|
||||||
|
|
||||||
|
-- | The 'Goalie' lifetime edit menu
|
||||||
|
editGoalieLtMenu :: Menu ()
|
||||||
|
editGoalieLtMenu = editMenu
|
||||||
|
"*** EDIT GOALTENDER LIFETIME ***"
|
||||||
|
-- key, label, value
|
||||||
|
[ ( '1', "Edit lifetime games", EGLtGames )
|
||||||
|
, ( '2', "Edit lifetime minutes", EGLtMins )
|
||||||
|
, ( '3', "Edit lifetime goals", EGLtGoals )
|
||||||
|
, ( '4', "Edit lifetime wins", EGLtWins )
|
||||||
|
, ( '5', "Edit lifetime losses", EGLtLosses )
|
||||||
|
, ( '6', "Edit lifetime ties", EGLtTies )
|
||||||
|
, ( 'R', "Return to edit menu", EGMenu )
|
||||||
|
]
|
||||||
|
|
||||||
|
editMenu :: String -> [(Char, String, EditGoalieMode)] -> Menu ()
|
||||||
|
editMenu title = Menu title () . map
|
||||||
|
(\(key, label, val) -> MenuItem key label $
|
||||||
|
modify $ progMode.editGoalieStateL.egsMode .~ val)
|
|
@ -0,0 +1,120 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
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.Prompt.EditGoalie
|
||||||
|
( goalieToEditPrompt
|
||||||
|
, editGoalieNumberPrompt
|
||||||
|
, editGoalieNamePrompt
|
||||||
|
, editGoalieYtdGamesPrompt
|
||||||
|
, editGoalieYtdMinsPrompt
|
||||||
|
, editGoalieYtdGoalsPrompt
|
||||||
|
, editGoalieYtdWinsPrompt
|
||||||
|
, editGoalieYtdLossesPrompt
|
||||||
|
, editGoalieYtdTiesPrompt
|
||||||
|
, editGoalieLtGamesPrompt
|
||||||
|
, editGoalieLtMinsPrompt
|
||||||
|
, editGoalieLtGoalsPrompt
|
||||||
|
, editGoalieLtWinsPrompt
|
||||||
|
, editGoalieLtLossesPrompt
|
||||||
|
, editGoalieLtTiesPrompt
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (modify)
|
||||||
|
import Lens.Micro ((.~))
|
||||||
|
|
||||||
|
import Mtlstats.Actions.EditGoalie
|
||||||
|
import Mtlstats.Prompt
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
-- | Prompt to select a 'Goalie' for editing
|
||||||
|
goalieToEditPrompt :: Prompt
|
||||||
|
goalieToEditPrompt = selectGoaliePrompt "Goalie to edit: " $
|
||||||
|
modify . (progMode.editGoalieStateL.egsSelectedGoalie .~)
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's number
|
||||||
|
editGoalieNumberPrompt :: Prompt
|
||||||
|
editGoalieNumberPrompt = numPrompt "Goalie number: " $
|
||||||
|
modify . editGoalieNumber
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's name
|
||||||
|
editGoalieNamePrompt :: Prompt
|
||||||
|
editGoalieNamePrompt = strPrompt "Goalie name: " $
|
||||||
|
modify . editGoalieName
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD games played
|
||||||
|
editGoalieYtdGamesPrompt :: Prompt
|
||||||
|
editGoalieYtdGamesPrompt = numPrompt "Year-to-date games played: " $
|
||||||
|
modify . editGoalieYtdGames
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD minutes played
|
||||||
|
editGoalieYtdMinsPrompt :: Prompt
|
||||||
|
editGoalieYtdMinsPrompt = numPrompt "Year-to-date minutes played: " $
|
||||||
|
modify . editGoalieYtdMins
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD goales allowed
|
||||||
|
editGoalieYtdGoalsPrompt :: Prompt
|
||||||
|
editGoalieYtdGoalsPrompt = numPrompt "Year-to-date goals allowed: " $
|
||||||
|
modify . editGoalieYtdGoals
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD wins
|
||||||
|
editGoalieYtdWinsPrompt :: Prompt
|
||||||
|
editGoalieYtdWinsPrompt = numPrompt "Year-to-date wins: " $
|
||||||
|
modify . editGoalieYtdWins
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD losses
|
||||||
|
editGoalieYtdLossesPrompt :: Prompt
|
||||||
|
editGoalieYtdLossesPrompt = numPrompt "Year-to-date losses: " $
|
||||||
|
modify . editGoalieYtdLosses
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's YTD ties
|
||||||
|
editGoalieYtdTiesPrompt :: Prompt
|
||||||
|
editGoalieYtdTiesPrompt = numPrompt "Year-to-date ties: " $
|
||||||
|
modify . editGoalieYtdTies
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime games played
|
||||||
|
editGoalieLtGamesPrompt :: Prompt
|
||||||
|
editGoalieLtGamesPrompt = numPrompt "Lifetime games played: " $
|
||||||
|
modify . editGoalieLtGames
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime minutes played
|
||||||
|
editGoalieLtMinsPrompt :: Prompt
|
||||||
|
editGoalieLtMinsPrompt = numPrompt "Lifetime minutes played: " $
|
||||||
|
modify . editGoalieLtMins
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime goals allowed
|
||||||
|
editGoalieLtGoalsPrompt :: Prompt
|
||||||
|
editGoalieLtGoalsPrompt = numPrompt "Lifetime goals allowed: " $
|
||||||
|
modify . editGoalieLtGoals
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime wins
|
||||||
|
editGoalieLtWinsPrompt :: Prompt
|
||||||
|
editGoalieLtWinsPrompt = numPrompt "Lifetime wins: " $
|
||||||
|
modify . editGoalieLtWins
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime losses
|
||||||
|
editGoalieLtLossesPrompt :: Prompt
|
||||||
|
editGoalieLtLossesPrompt = numPrompt "Lifetime losses: " $
|
||||||
|
modify . editGoalieLtLosses
|
||||||
|
|
||||||
|
-- | Prompt to edit a goalie's lifetime ties
|
||||||
|
editGoalieLtTiesPrompt :: Prompt
|
||||||
|
editGoalieLtTiesPrompt = numPrompt "Lifetime ties: " $
|
||||||
|
modify . editGoalieLtTies
|
|
@ -33,6 +33,8 @@ module Mtlstats.Types (
|
||||||
CreateGoalieState (..),
|
CreateGoalieState (..),
|
||||||
EditPlayerState (..),
|
EditPlayerState (..),
|
||||||
EditPlayerMode (..),
|
EditPlayerMode (..),
|
||||||
|
EditGoalieState (..),
|
||||||
|
EditGoalieMode (..),
|
||||||
Database (..),
|
Database (..),
|
||||||
Player (..),
|
Player (..),
|
||||||
PlayerStats (..),
|
PlayerStats (..),
|
||||||
|
@ -52,6 +54,7 @@ module Mtlstats.Types (
|
||||||
createPlayerStateL,
|
createPlayerStateL,
|
||||||
createGoalieStateL,
|
createGoalieStateL,
|
||||||
editPlayerStateL,
|
editPlayerStateL,
|
||||||
|
editGoalieStateL,
|
||||||
-- ** GameState Lenses
|
-- ** GameState Lenses
|
||||||
gameYear,
|
gameYear,
|
||||||
gameMonth,
|
gameMonth,
|
||||||
|
@ -89,6 +92,9 @@ module Mtlstats.Types (
|
||||||
-- ** EditPlayerState Lenses
|
-- ** EditPlayerState Lenses
|
||||||
epsSelectedPlayer,
|
epsSelectedPlayer,
|
||||||
epsMode,
|
epsMode,
|
||||||
|
-- ** EditGoalieState Lenses
|
||||||
|
egsSelectedGoalie,
|
||||||
|
egsMode,
|
||||||
-- ** Database Lenses
|
-- ** Database Lenses
|
||||||
dbPlayers,
|
dbPlayers,
|
||||||
dbGoalies,
|
dbGoalies,
|
||||||
|
@ -129,6 +135,7 @@ module Mtlstats.Types (
|
||||||
newCreatePlayerState,
|
newCreatePlayerState,
|
||||||
newCreateGoalieState,
|
newCreateGoalieState,
|
||||||
newEditPlayerState,
|
newEditPlayerState,
|
||||||
|
newEditGoalieState,
|
||||||
newDatabase,
|
newDatabase,
|
||||||
newPlayer,
|
newPlayer,
|
||||||
newPlayerStats,
|
newPlayerStats,
|
||||||
|
@ -218,6 +225,7 @@ data ProgMode
|
||||||
| CreatePlayer CreatePlayerState
|
| CreatePlayer CreatePlayerState
|
||||||
| CreateGoalie CreateGoalieState
|
| CreateGoalie CreateGoalieState
|
||||||
| EditPlayer EditPlayerState
|
| EditPlayer EditPlayerState
|
||||||
|
| EditGoalie EditGoalieState
|
||||||
|
|
||||||
instance Show ProgMode where
|
instance Show ProgMode where
|
||||||
show MainMenu = "MainMenu"
|
show MainMenu = "MainMenu"
|
||||||
|
@ -226,6 +234,7 @@ instance Show ProgMode where
|
||||||
show (CreatePlayer _) = "CreatePlayer"
|
show (CreatePlayer _) = "CreatePlayer"
|
||||||
show (CreateGoalie _) = "CreateGoalie"
|
show (CreateGoalie _) = "CreateGoalie"
|
||||||
show (EditPlayer _) = "EditPlayer"
|
show (EditPlayer _) = "EditPlayer"
|
||||||
|
show (EditGoalie _) = "EditGoalie"
|
||||||
|
|
||||||
-- | The game state
|
-- | The game state
|
||||||
data GameState = GameState
|
data GameState = GameState
|
||||||
|
@ -334,6 +343,34 @@ data EditPlayerMode
|
||||||
| EPLtPMin
|
| EPLtPMin
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
-- | 'Goalie' edit status
|
||||||
|
data EditGoalieState = EditGoalieState
|
||||||
|
{ _egsSelectedGoalie :: Maybe Int
|
||||||
|
-- ^ The index number of the 'Goalie' being edited
|
||||||
|
, _egsMode :: EditGoalieMode
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | 'Goalie' editing mode
|
||||||
|
data EditGoalieMode
|
||||||
|
= EGMenu
|
||||||
|
| EGNumber
|
||||||
|
| EGName
|
||||||
|
| EGYtd
|
||||||
|
| EGLifetime
|
||||||
|
| EGYtdGames
|
||||||
|
| EGYtdMins
|
||||||
|
| EGYtdGoals
|
||||||
|
| EGYtdWins
|
||||||
|
| EGYtdLosses
|
||||||
|
| EGYtdTies
|
||||||
|
| EGLtGames
|
||||||
|
| EGLtMins
|
||||||
|
| EGLtGoals
|
||||||
|
| EGLtWins
|
||||||
|
| EGLtLosses
|
||||||
|
| EGLtTies
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
-- | Represents the database
|
-- | Represents the database
|
||||||
data Database = Database
|
data Database = Database
|
||||||
{ _dbPlayers :: [Player]
|
{ _dbPlayers :: [Player]
|
||||||
|
@ -581,6 +618,7 @@ makeLenses ''GameState
|
||||||
makeLenses ''CreatePlayerState
|
makeLenses ''CreatePlayerState
|
||||||
makeLenses ''CreateGoalieState
|
makeLenses ''CreateGoalieState
|
||||||
makeLenses ''EditPlayerState
|
makeLenses ''EditPlayerState
|
||||||
|
makeLenses ''EditGoalieState
|
||||||
makeLenses ''Database
|
makeLenses ''Database
|
||||||
makeLenses ''Player
|
makeLenses ''Player
|
||||||
makeLenses ''PlayerStats
|
makeLenses ''PlayerStats
|
||||||
|
@ -616,6 +654,13 @@ editPlayerStateL = lens
|
||||||
_ -> newEditPlayerState)
|
_ -> newEditPlayerState)
|
||||||
(\_ eps -> EditPlayer eps)
|
(\_ eps -> EditPlayer eps)
|
||||||
|
|
||||||
|
editGoalieStateL :: Lens' ProgMode EditGoalieState
|
||||||
|
editGoalieStateL = lens
|
||||||
|
(\case
|
||||||
|
EditGoalie egs -> egs
|
||||||
|
_ -> newEditGoalieState)
|
||||||
|
(\_ egs -> EditGoalie egs)
|
||||||
|
|
||||||
-- | Constructor for a 'ProgState'
|
-- | Constructor for a 'ProgState'
|
||||||
newProgState :: ProgState
|
newProgState :: ProgState
|
||||||
newProgState = ProgState
|
newProgState = ProgState
|
||||||
|
@ -678,6 +723,13 @@ newEditPlayerState = EditPlayerState
|
||||||
, _epsMode = EPMenu
|
, _epsMode = EPMenu
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Constructor for an 'EditGoalieState' value
|
||||||
|
newEditGoalieState :: EditGoalieState
|
||||||
|
newEditGoalieState = EditGoalieState
|
||||||
|
{ _egsSelectedGoalie = Nothing
|
||||||
|
, _egsMode = EGMenu
|
||||||
|
}
|
||||||
|
|
||||||
-- | Constructor for a 'Database'
|
-- | Constructor for a 'Database'
|
||||||
newDatabase :: Database
|
newDatabase :: Database
|
||||||
newDatabase = Database
|
newDatabase = Database
|
||||||
|
|
|
@ -0,0 +1,537 @@
|
||||||
|
{-
|
||||||
|
|
||||||
|
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
|
|
@ -38,6 +38,7 @@ 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
|
||||||
|
|
||||||
|
@ -51,6 +52,7 @@ spec = describe "Mtlstats.Actions" $ do
|
||||||
createPlayerSpec
|
createPlayerSpec
|
||||||
createGoalieSpec
|
createGoalieSpec
|
||||||
editPlayerSpec
|
editPlayerSpec
|
||||||
|
editGoalieSpec
|
||||||
addPlayerSpec
|
addPlayerSpec
|
||||||
addGoalieSpec
|
addGoalieSpec
|
||||||
resetCreatePlayerStateSpec
|
resetCreatePlayerStateSpec
|
||||||
|
@ -59,6 +61,7 @@ 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
|
||||||
|
@ -165,6 +168,12 @@ editPlayerSpec = describe "editPlayer" $
|
||||||
s = editPlayer newProgState
|
s = editPlayer newProgState
|
||||||
in show (s^.progMode) `shouldBe` "EditPlayer"
|
in show (s^.progMode) `shouldBe` "EditPlayer"
|
||||||
|
|
||||||
|
editGoalieSpec :: Spec
|
||||||
|
editGoalieSpec = describe "editGoalie" $
|
||||||
|
it "should change the mode appropriately" $ let
|
||||||
|
s = editGoalie newProgState
|
||||||
|
in show (s^.progMode) `shouldBe` "EditGoalie"
|
||||||
|
|
||||||
addPlayerSpec :: Spec
|
addPlayerSpec :: Spec
|
||||||
addPlayerSpec = describe "addPlayer" $ do
|
addPlayerSpec = describe "addPlayer" $ do
|
||||||
let
|
let
|
||||||
|
|
|
@ -56,6 +56,7 @@ spec = describe "Mtlstats.Types" $ do
|
||||||
createPlayerStateLSpec
|
createPlayerStateLSpec
|
||||||
createGoalieStateLSpec
|
createGoalieStateLSpec
|
||||||
editPlayerStateLSpec
|
editPlayerStateLSpec
|
||||||
|
editGoalieStateLSpec
|
||||||
teamScoreSpec
|
teamScoreSpec
|
||||||
otherScoreSpec
|
otherScoreSpec
|
||||||
homeTeamSpec
|
homeTeamSpec
|
||||||
|
@ -169,6 +170,24 @@ editPlayerStateLSpec = describe "editPlayerStateL" $
|
||||||
eps2 = newEditPlayerState
|
eps2 = newEditPlayerState
|
||||||
& epsSelectedPlayer ?~ 2
|
& epsSelectedPlayer ?~ 2
|
||||||
|
|
||||||
|
editGoalieStateLSpec :: Spec
|
||||||
|
editGoalieStateLSpec = describe "editGoalieStateL" $
|
||||||
|
lensSpec editGoalieStateL
|
||||||
|
-- getters
|
||||||
|
[ ( "missing state", MainMenu, newEditGoalieState )
|
||||||
|
, ( "with state", EditGoalie egs1, egs1 )
|
||||||
|
]
|
||||||
|
-- setters
|
||||||
|
[ ( "set state", MainMenu, egs1 )
|
||||||
|
, ( "change state", EditGoalie egs1, egs2 )
|
||||||
|
, ( "clear state", EditGoalie egs1, newEditGoalieState )
|
||||||
|
]
|
||||||
|
where
|
||||||
|
egs1 = newEditGoalieState
|
||||||
|
& egsSelectedGoalie ?~ 1
|
||||||
|
egs2 = newEditGoalieState
|
||||||
|
& egsSelectedGoalie ?~ 2
|
||||||
|
|
||||||
teamScoreSpec :: Spec
|
teamScoreSpec :: Spec
|
||||||
teamScoreSpec = describe "teamScore" $ do
|
teamScoreSpec = describe "teamScore" $ do
|
||||||
let
|
let
|
||||||
|
@ -858,6 +877,17 @@ instance Comparable EditPlayerState where
|
||||||
it ("should be " ++ show (expected^.epsMode)) $
|
it ("should be " ++ show (expected^.epsMode)) $
|
||||||
actual^.epsMode `shouldBe` expected^.epsMode
|
actual^.epsMode `shouldBe` expected^.epsMode
|
||||||
|
|
||||||
|
instance Comparable EditGoalieState where
|
||||||
|
compareTest actual expected = do
|
||||||
|
|
||||||
|
describe "egsSelectedGoalie" $
|
||||||
|
it ("should be " ++ show (expected^.egsSelectedGoalie)) $
|
||||||
|
actual^.egsSelectedGoalie `shouldBe` expected^.egsSelectedGoalie
|
||||||
|
|
||||||
|
describe "egsMode" $
|
||||||
|
it ("should be " ++ show (expected^.egsMode)) $
|
||||||
|
actual^.egsMode `shouldBe` expected^.egsMode
|
||||||
|
|
||||||
instance Comparable CreateGoalieState where
|
instance Comparable CreateGoalieState where
|
||||||
compareTest actual expected = do
|
compareTest actual expected = do
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue
Block a user