34 Commits

Author SHA1 Message Date
Jonathan Lamothe
29fae81513 version 0.13.0 2020-03-05 05:21:34 -05:00
Jonathan Lamothe
0676bf4067 Merge pull request #76 from mtlstats/single-goalie
don't ask which goalie to assign the game to when there's only one
2020-02-14 23:02:47 -05:00
Jonathan Lamothe
119032ca80 don't ask which goalie to assign the game to when there's only one 2020-02-14 22:56:35 -05:00
Jonathan Lamothe
2607fc5ce8 Merge pull request #75 from mtlstats/active-check
ask whether player/goalie is active on creation
2020-02-14 00:15:17 -05:00
Jonathan Lamothe
d18cb7dd59 updated change log 2020-02-14 00:09:34 -05:00
Jonathan Lamothe
dff11a8316 assume goalie is active on creation of rookie 2020-02-14 00:08:19 -05:00
Jonathan Lamothe
747bdf8f32 assume player is active on creation of rookie 2020-02-14 00:08:19 -05:00
Jonathan Lamothe
9b07c6d249 record active flag on goalie creation 2020-02-13 23:55:00 -05:00
Jonathan Lamothe
e28ef1ff0e record active flag on player creation 2020-02-13 23:40:43 -05:00
Jonathan Lamothe
960fbb3443 display active flags in new player/goalie creation summaries 2020-02-13 23:30:31 -05:00
Jonathan Lamothe
439aab99d3 prompt whether or not a new player/goalie is active 2020-02-13 23:28:10 -05:00
Jonathan Lamothe
8d7a7997b1 created active flag controller branches 2020-02-13 23:23:18 -05:00
Jonathan Lamothe
7e409fdbd4 added cpsActiveFlag and cgsActiveFlag 2020-02-13 23:18:53 -05:00
Jonathan Lamothe
28b1fa0e06 Merge pull request #74 from mtlstats/rookie-check
Rookie check
2020-02-13 20:20:46 -05:00
Jonathan Lamothe
7c4b7331e8 updated change log 2020-02-13 20:12:00 -05:00
Jonathan Lamothe
214710661a code cleanup 2020-02-13 20:08:10 -05:00
Jonathan Lamothe
6bb4601e6b only ask for goalie lifetime stats when not rookie 2020-02-13 20:03:27 -05:00
Jonathan Lamothe
e51953650c set rookie flag appropriately on goalie creation 2020-02-13 19:45:36 -05:00
Jonathan Lamothe
14386f9c7d display whether or not goalie is a rookie on creation confirmation 2020-02-13 15:23:40 -05:00
Jonathan Lamothe
ec10aa7998 ask if a new goalie is a rookie 2020-02-13 14:57:29 -05:00
Jonathan Lamothe
fe28e96145 use promptController in Mtlstats.Control.CreateGoalie 2020-02-13 14:45:43 -05:00
Jonathan Lamothe
2941998058 only edit player lifetime stats if rookie
...on new player creation
2020-02-13 11:08:32 -05:00
Jonathan Lamothe
c22849bb3b set rookie flag on player creation 2020-02-13 10:35:35 -05:00
Jonathan Lamothe
4315b40732 added rookie flag to player creation confirmation 2020-02-13 03:24:11 -05:00
Jonathan Lamothe
fefa217df1 implemented Mtlstats.Control.CreatePlayer.getRookieFlagC
...also refactored some other controllers to use promptController
2020-02-13 02:55:51 -05:00
Jonathan Lamothe
6d77caaa14 added cpsRookieFlag and cgsRookieFlag 2020-02-13 02:31:20 -05:00
Jonathan Lamothe
a69853858d Merge pull request #73 from mtlstats/position-shortcuts
autocompletion of player positions
2020-02-13 02:20:39 -05:00
Jonathan Lamothe
045f2915e1 updated change log 2020-02-13 02:00:52 -05:00
Jonathan Lamothe
dfd226c7bd implement position selection prompt on player creation/edit 2020-02-13 01:58:59 -05:00
Jonathan Lamothe
b9d8b263df implemented posCallback 2020-02-13 01:39:56 -05:00
Jonathan Lamothe
a2968595d8 implemented posSearchExact 2020-02-12 00:27:28 -05:00
Jonathan Lamothe
25e4929f0b implemented posSearch 2020-02-11 23:58:47 -05:00
Jonathan Lamothe
457298e565 implemented getPositions 2020-02-11 23:37:43 -05:00
Jonathan Lamothe
a80eaa2a40 implemented selectPositionPrompt 2020-02-11 23:00:13 -05:00
14 changed files with 452 additions and 119 deletions

View File

@@ -1,5 +1,11 @@
# Changelog for mtlstats # Changelog for mtlstats
## 0.13.0
- Added autocomplete to player position prompt
- Don't prompt for lifetime stats on rookie player/goalie creation
- Ask whether a player/goalie is active on creation
- Don't ask which goalie to assign the game to when there's only one
## 0.12.0 ## 0.12.0
- Edit lifetime stats on new player/goalie creation - Edit lifetime stats on new player/goalie creation
- Sort goalies by minutes played - Sort goalies by minutes played

View File

@@ -1,5 +1,5 @@
name: mtlstats name: mtlstats
version: 0.12.0 version: 0.13.0
github: "mtlstats/mtlstats" github: "mtlstats/mtlstats"
license: GPL-3 license: GPL-3
author: "Jonathan Lamothe" author: "Jonathan Lamothe"

View File

@@ -162,10 +162,14 @@ addPlayer :: ProgState -> ProgState
addPlayer s = fromMaybe s $ do addPlayer s = fromMaybe s $ do
let cps = s^.progMode.createPlayerStateL let cps = s^.progMode.createPlayerStateL
num <- cps^.cpsNumber num <- cps^.cpsNumber
rFlag <- cps^.cpsRookieFlag
aFlag <- cps^.cpsActiveFlag
let let
name = cps^.cpsName name = cps^.cpsName
pos = cps^.cpsPosition pos = cps^.cpsPosition
player = newPlayer num name pos player = newPlayer num name pos
& pRookie .~ rFlag
& pActive .~ aFlag
Just $ s & database.dbPlayers Just $ s & database.dbPlayers
%~ (++[player]) %~ (++[player])
@@ -174,9 +178,13 @@ addGoalie :: ProgState -> ProgState
addGoalie s = fromMaybe s $ do addGoalie s = fromMaybe s $ do
let cgs = s^.progMode.createGoalieStateL let cgs = s^.progMode.createGoalieStateL
num <- cgs^.cgsNumber num <- cgs^.cgsNumber
rFlag <- cgs^.cgsRookieFlag
aFlag <- cgs^.cgsActiveFlag
let let
name = cgs^.cgsName name = cgs^.cgsName
goalie = newGoalie num name goalie = newGoalie num name
& gRookie .~ rFlag
& gActive .~ aFlag
Just $ s & database.dbGoalies Just $ s & database.dbGoalies
%~ (++[goalie]) %~ (++[goalie])

View File

@@ -36,8 +36,12 @@ import Mtlstats.Util
-- | Attempts to finish game goalie entry -- | Attempts to finish game goalie entry
finishGoalieEntry :: ProgState -> ProgState finishGoalieEntry :: ProgState -> ProgState
finishGoalieEntry s = s & progMode.gameStateL.gameGoaliesRecorded finishGoalieEntry s = case M.toList $ s^.progMode.gameStateL.gameGoalieStats of
.~ not (null $ s^.progMode.gameStateL.gameGoalieStats) [] -> s
[(gid, _)] -> setGameGoalie gid s'
_ -> s'
where
s' = s & progMode.gameStateL.gameGoaliesRecorded .~ True
-- | Records the goalie's game stats -- | Records the goalie's game stats
recordGoalieStats :: ProgState -> ProgState recordGoalieStats :: ProgState -> ProgState

View File

@@ -21,13 +21,12 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Control.CreateGoalie (createGoalieC) where module Mtlstats.Control.CreateGoalie (createGoalieC) where
import Control.Monad (join)
import Control.Monad.Trans.State (gets, modify) import Control.Monad.Trans.State (gets, modify)
import Data.Maybe (fromJust)
import Lens.Micro ((^.), (.~), (?~), (%~), to) import Lens.Micro ((^.), (.~), (?~), (%~), to)
import qualified UI.NCurses as C import qualified UI.NCurses as C
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Format
import Mtlstats.Handlers import Mtlstats.Handlers
import Mtlstats.Prompt import Mtlstats.Prompt
import Mtlstats.Types import Mtlstats.Types
@@ -37,21 +36,37 @@ createGoalieC :: CreateGoalieState -> Controller
createGoalieC cgs createGoalieC cgs
| null $ cgs^.cgsNumber = getGoalieNumC | null $ cgs^.cgsNumber = getGoalieNumC
| null $ cgs^.cgsName = getGoalieNameC | null $ cgs^.cgsName = getGoalieNameC
| null $ cgs^.cgsRookieFlag = getRookieFlagC
| null $ cgs^.cgsActiveFlag = getActiveFlagC
| otherwise = confirmCreateGoalieC | otherwise = confirmCreateGoalieC
getGoalieNumC :: Controller getGoalieNumC :: Controller
getGoalieNumC = Controller getGoalieNumC = promptController goalieNumPrompt
{ drawController = drawPrompt goalieNumPrompt
getGoalieNameC :: Controller
getGoalieNameC = promptController goalieNamePrompt
getRookieFlagC :: Controller
getRookieFlagC = Controller
{ drawController = const $ do
C.drawString "Is this goalie a rookie? (Y/N)"
return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
promptHandler goalieNumPrompt e modify $ case ynHandler e of
Just True -> progMode.createGoalieStateL
%~ (cgsRookieFlag ?~ True)
. (cgsActiveFlag ?~ True)
rf -> progMode.createGoalieStateL.cgsRookieFlag .~ rf
return True return True
} }
getGoalieNameC :: Controller getActiveFlagC :: Controller
getGoalieNameC = Controller getActiveFlagC = Controller
{ drawController = drawPrompt goalieNamePrompt { drawController = const $ do
C.drawString "Is this goalie active? (Y/N)"
return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
promptHandler goalieNamePrompt e modify $ progMode.createGoalieStateL.cgsActiveFlag .~ ynHandler e
return True return True
} }
@@ -60,25 +75,33 @@ confirmCreateGoalieC = Controller
{ drawController = \s -> do { drawController = \s -> do
let cgs = s^.progMode.createGoalieStateL let cgs = s^.progMode.createGoalieStateL
C.drawString $ unlines C.drawString $ unlines
[ "Goalie number: " ++ show (fromJust $ cgs^.cgsNumber) $ labelTable
, " Goalie name: " ++ cgs^.cgsName [ ( "Goalie number", maybe "?" show $ cgs^.cgsNumber )
, "" , ( "Goalie name", cgs^.cgsName )
, ( "Rookie", maybe "?" show $ cgs^.cgsRookieFlag )
, ( "Active", maybe "?" show $ cgs^.cgsActiveFlag )
]
++ [ ""
, "Create goalie: are you sure? (Y/N)" , "Create goalie: are you sure? (Y/N)"
] ]
return C.CursorInvisible return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
cgs <- gets (^.progMode.createGoalieStateL)
let
success = cgs^.cgsSuccessCallback
failure = cgs^.cgsFailureCallback
case ynHandler e of case ynHandler e of
Just True -> do Just True -> do
gid <- gets (^.database.dbGoalies.to length) gid <- gets (^.database.dbGoalies.to length)
cb <- gets (^.progMode.createGoalieStateL.cgsSuccessCallback) let rookie = cgs^.cgsRookieFlag == Just True
modify modify addGoalie
$ (progMode.editGoalieStateL if rookie
then success
else modify $ progMode.editGoalieStateL
%~ (egsSelectedGoalie ?~ gid) %~ (egsSelectedGoalie ?~ gid)
. (egsMode .~ EGLtGames True) . (egsMode .~ EGLtGames True)
. (egsCallback .~ cb)) . (egsCallback .~ success)
. addGoalie Just False -> failure
Just False ->
join $ gets (^.progMode.createGoalieStateL.cgsFailureCallback)
Nothing -> return () Nothing -> return ()
return True return True
} }

View File

@@ -21,13 +21,12 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Control.CreatePlayer (createPlayerC) where module Mtlstats.Control.CreatePlayer (createPlayerC) where
import Control.Monad (join)
import Control.Monad.Trans.State (gets, modify) import Control.Monad.Trans.State (gets, modify)
import Data.Maybe (fromJust)
import Lens.Micro ((^.), (.~), (?~), (%~), to) import Lens.Micro ((^.), (.~), (?~), (%~), to)
import qualified UI.NCurses as C import qualified UI.NCurses as C
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Format
import Mtlstats.Handlers import Mtlstats.Handlers
import Mtlstats.Prompt import Mtlstats.Prompt
import Mtlstats.Types import Mtlstats.Types
@@ -38,29 +37,40 @@ createPlayerC cps
| null $ cps^.cpsNumber = getPlayerNumC | null $ cps^.cpsNumber = getPlayerNumC
| null $ cps^.cpsName = getPlayerNameC | null $ cps^.cpsName = getPlayerNameC
| null $ cps^.cpsPosition = getPlayerPosC | null $ cps^.cpsPosition = getPlayerPosC
| null $ cps^.cpsRookieFlag = getRookieFlagC
| null $ cps^.cpsActiveFlag = getActiveFlagC
| otherwise = confirmCreatePlayerC | otherwise = confirmCreatePlayerC
getPlayerNumC :: Controller getPlayerNumC :: Controller
getPlayerNumC = Controller getPlayerNumC = promptController playerNumPrompt
{ drawController = drawPrompt playerNumPrompt
, handleController = \e -> do
promptHandler playerNumPrompt e
return True
}
getPlayerNameC :: Controller getPlayerNameC :: Controller
getPlayerNameC = Controller getPlayerNameC = promptController playerNamePrompt
{ drawController = drawPrompt playerNamePrompt
getPlayerPosC :: Controller
getPlayerPosC = promptController playerPosPrompt
getRookieFlagC :: Controller
getRookieFlagC = Controller
{ drawController = const $ do
C.drawString "Is this player a rookie? (Y/N)"
return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
promptHandler playerNamePrompt e modify $ case ynHandler e of
Just True -> progMode.createPlayerStateL
%~ (cpsRookieFlag ?~ True)
. (cpsActiveFlag ?~ True)
rf -> progMode.createPlayerStateL.cpsRookieFlag .~ rf
return True return True
} }
getPlayerPosC :: Controller getActiveFlagC :: Controller
getPlayerPosC = Controller getActiveFlagC = Controller
{ drawController = drawPrompt playerPosPrompt { drawController = const $ do
C.drawString "Is the player active? (Y/N)"
return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
promptHandler playerPosPrompt e modify $ progMode.createPlayerStateL.cpsActiveFlag .~ ynHandler e
return True return True
} }
@@ -68,24 +78,35 @@ confirmCreatePlayerC :: Controller
confirmCreatePlayerC = Controller confirmCreatePlayerC = Controller
{ drawController = \s -> do { drawController = \s -> do
let cps = s^.progMode.createPlayerStateL let cps = s^.progMode.createPlayerStateL
C.drawString $ " Player number: " ++ show (fromJust $ cps^.cpsNumber) ++ "\n" C.drawString $ unlines
C.drawString $ " Player name: " ++ cps^.cpsName ++ "\n" $ labelTable
C.drawString $ "Player position: " ++ cps^.cpsPosition ++ "\n\n" [ ( "Player number", maybe "?" show $ cps^.cpsNumber )
C.drawString "Create player: are you sure? (Y/N)" , ( "Player name", cps^.cpsName )
, ( "Player position", cps^.cpsPosition )
, ( "Rookie", maybe "?" show $ cps^.cpsRookieFlag )
, ( "Active", maybe "?" show $ cps^.cpsActiveFlag )
]
++ [ ""
, "Create player: are you sure? (Y/N)"
]
return C.CursorInvisible return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
cps <- gets (^.progMode.createPlayerStateL)
let
success = cps^.cpsSuccessCallback
failure = cps^.cpsFailureCallback
case ynHandler e of case ynHandler e of
Just True -> do Just True -> do
pid <- gets (^.database.dbPlayers.to length) pid <- gets (^.database.dbPlayers.to length)
cb <- gets (^.progMode.createPlayerStateL.cpsSuccessCallback) let rookie = cps^.cpsRookieFlag == Just True
modify modify addPlayer
$ (progMode.editPlayerStateL if rookie
then success
else modify $ progMode.editPlayerStateL
%~ (epsSelectedPlayer ?~ pid) %~ (epsSelectedPlayer ?~ pid)
. (epsMode .~ EPLtGoals True) . (epsMode .~ EPLtGoals True)
. (epsCallback .~ cb)) . (epsCallback .~ success)
. addPlayer Just False -> failure
Just False ->
join $ gets (^.progMode.createPlayerStateL.cpsFailureCallback)
Nothing -> return () Nothing -> return ()
return True return True
} }

View File

@@ -0,0 +1,89 @@
{- |
mtlstats
Copyright (C) 1984, 1985, 2019, 2020 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.Helpers.Position
( posSearch
, posSearchExact
, posCallback
, getPositions
) where
import Control.Monad.Trans.State (gets)
import Data.Char (toUpper)
import Data.List (isInfixOf)
import Data.Maybe (fromMaybe)
import qualified Data.Set as S
import Lens.Micro ((^.), to)
import Mtlstats.Types
import Mtlstats.Util
-- | Searches the 'Database' for all the positions used
posSearch
:: String
-- ^ The search string
-> Database
-- ^ The database
-> [(Int, String)]
-- ^ A list of result indices and their values
posSearch sStr db = filter sFunc $ zip [0..] ps
where
sFunc (_, pos) = map toUpper sStr `isInfixOf` map toUpper pos
ps = getPositions db
-- | Searches the 'Database' for an exact position
posSearchExact
:: String
-- ^ The search string
-> Database
-- ^ The database
-> Maybe Int
-- ^ The index of the result (or 'Nothing' if not found)
posSearchExact sStr db = case filter sFunc $ zip [0..] ps of
[] -> Nothing
(n,_):_ -> Just n
where
sFunc (_, pos) = sStr == pos
ps = getPositions db
-- | Builds a callback function for when a 'Player' position is
-- selected
posCallback
:: (String -> Action ())
-- ^ The raw callback function
-> Maybe Int
-- ^ The index number of the position selected or 'Nothing' if blank
-> Action ()
-- ^ The action to perform
posCallback callback = \case
Nothing -> callback ""
Just n -> do
ps <- gets (^.database.to getPositions)
let pos = fromMaybe "" $ nth n ps
callback pos
-- | Extracts a list of positions from a 'Database'
getPositions :: Database -> [String]
getPositions = do
raw <- map (^.pPosition) . (^.dbPlayers)
return $ S.toList $ S.fromList raw

View File

@@ -42,6 +42,7 @@ module Mtlstats.Prompt (
goalieNamePrompt, goalieNamePrompt,
selectPlayerPrompt, selectPlayerPrompt,
selectGoaliePrompt, selectGoaliePrompt,
selectPositionPrompt,
playerToEditPrompt playerToEditPrompt
) where ) where
@@ -56,6 +57,7 @@ import qualified UI.NCurses as C
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Config import Mtlstats.Config
import Mtlstats.Helpers.Position
import Mtlstats.Types import Mtlstats.Types
import Mtlstats.Util import Mtlstats.Util
@@ -236,7 +238,7 @@ playerNamePrompt = namePrompt "Player name: " $
-- | Prompts for a new player's position -- | Prompts for a new player's position
playerPosPrompt :: Prompt playerPosPrompt :: Prompt
playerPosPrompt = ucStrPrompt "Player position: " $ playerPosPrompt = selectPositionPrompt "Player position: " $
modify . (progMode.createPlayerStateL.cpsPosition .~) modify . (progMode.createPlayerStateL.cpsPosition .~)
-- | Prompts tor the goalie's number -- | Prompts tor the goalie's number
@@ -307,6 +309,24 @@ selectGoaliePrompt pStr callback = selectPrompt SelectParams
modify $ progMode .~ CreateGoalie cgs modify $ progMode .~ CreateGoalie cgs
} }
-- | Selects (or creates) a player position
selectPositionPrompt
:: String
-- ^ The 'Prompt' string
-> (String -> Action ())
-- ^ The action to perform when a value is entered
-> Prompt
selectPositionPrompt pStr callback = selectPrompt SelectParams
{ spPrompt = pStr
, spSearchHeader = "Positions:"
, spSearch = posSearch
, spSearchExact = posSearchExact
, spElemDesc = id
, spProcessChar = \ch -> (++ [toUpper ch])
, spCallback = posCallback callback
, spNotFound = callback
}
playerToEditPrompt :: Prompt playerToEditPrompt :: Prompt
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $ playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~) modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)

View File

@@ -62,7 +62,7 @@ editPlayerPosPrompt
:: Action () :: Action ()
-- ^ The action to be performed upon completion -- ^ The action to be performed upon completion
-> Prompt -> Prompt
editPlayerPosPrompt callback = ucStrPrompt "Player position: " $ \pos -> do editPlayerPosPrompt callback = selectPositionPrompt "Player position: " $ \pos -> do
if null pos if null pos
then goto EPMenu then goto EPMenu
else doEdit EPMenu $ pPosition .~ pos else doEdit EPMenu $ pPosition .~ pos

View File

@@ -88,11 +88,15 @@ module Mtlstats.Types (
cpsNumber, cpsNumber,
cpsName, cpsName,
cpsPosition, cpsPosition,
cpsRookieFlag,
cpsActiveFlag,
cpsSuccessCallback, cpsSuccessCallback,
cpsFailureCallback, cpsFailureCallback,
-- ** CreateGoalieState Lenses -- ** CreateGoalieState Lenses
cgsNumber, cgsNumber,
cgsName, cgsName,
cgsRookieFlag,
cgsActiveFlag,
cgsSuccessCallback, cgsSuccessCallback,
cgsFailureCallback, cgsFailureCallback,
-- ** EditPlayerState Lenses -- ** EditPlayerState Lenses
@@ -328,6 +332,10 @@ data CreatePlayerState = CreatePlayerState
-- ^ The player's name -- ^ The player's name
, _cpsPosition :: String , _cpsPosition :: String
-- ^ The player's position -- ^ The player's position
, _cpsRookieFlag :: Maybe Bool
-- ^ Indicates whether or not the player is a rookie
, _cpsActiveFlag :: Maybe Bool
-- ^ Indicates whether or not the plauer is active
, _cpsSuccessCallback :: Action () , _cpsSuccessCallback :: Action ()
-- ^ The function to call on success -- ^ The function to call on success
, _cpsFailureCallback :: Action () , _cpsFailureCallback :: Action ()
@@ -340,6 +348,10 @@ data CreateGoalieState = CreateGoalieState
-- ^ The goalie's number -- ^ The goalie's number
, _cgsName :: String , _cgsName :: String
-- ^ The goalie's name -- ^ The goalie's name
, _cgsRookieFlag :: Maybe Bool
-- ^ Indicates whether or not the goalie is a rookie
, _cgsActiveFlag :: Maybe Bool
-- ^ Indicates whether or not the goalie is active
, _cgsSuccessCallback :: Action () , _cgsSuccessCallback :: Action ()
-- ^ The function to call on success -- ^ The function to call on success
, _cgsFailureCallback :: Action () , _cgsFailureCallback :: Action ()
@@ -807,6 +819,8 @@ newCreatePlayerState = CreatePlayerState
{ _cpsNumber = Nothing { _cpsNumber = Nothing
, _cpsName = "" , _cpsName = ""
, _cpsPosition = "" , _cpsPosition = ""
, _cpsRookieFlag = Nothing
, _cpsActiveFlag = Nothing
, _cpsSuccessCallback = return () , _cpsSuccessCallback = return ()
, _cpsFailureCallback = return () , _cpsFailureCallback = return ()
} }
@@ -816,6 +830,8 @@ newCreateGoalieState :: CreateGoalieState
newCreateGoalieState = CreateGoalieState newCreateGoalieState = CreateGoalieState
{ _cgsNumber = Nothing { _cgsNumber = Nothing
, _cgsName = "" , _cgsName = ""
, _cgsRookieFlag = Nothing
, _cgsActiveFlag = Nothing
, _cgsSuccessCallback = return () , _cgsSuccessCallback = return ()
, _cgsFailureCallback = return () , _cgsFailureCallback = return ()
} }

View File

@@ -23,7 +23,7 @@ module Actions.NewGame.GoalieInputSpec (spec) where
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
import Lens.Micro ((^.), (&), (.~), (?~)) import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import Test.Hspec (Spec, context, describe, it, shouldBe) import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Actions.NewGame.GoalieInput import Mtlstats.Actions.NewGame.GoalieInput
@@ -39,21 +39,44 @@ spec = describe "Mtlstats.Actions.GoalieInput" $ do
setGameGoalieSpec setGameGoalieSpec
finishGoalieEntrySpec :: Spec finishGoalieEntrySpec :: Spec
finishGoalieEntrySpec = describe "finishGoalieEntry" $ do finishGoalieEntrySpec = describe "finishGoalieEntry" $ mapM_
(\(label, stats, grFlag, gaFlag) -> context label $ do
let let
progState stats = newProgState ps = newProgState
& progMode.gameStateL.gameGoalieStats .~ stats & progMode.gameStateL
& finishGoalieEntry %~ (gameGoalieStats .~ stats)
. (gameType ?~ HomeGame)
. (homeScore ?~ 1)
. (awayScore ?~ 0)
. (overtimeFlag ?~ False)
& database.dbGoalies .~ goalies
context "no goalie data" $ ps' = finishGoalieEntry ps
it "should not set goaliesRecorded" $ let gs = ps'^.progMode.gameStateL
s = progState M.empty
in s^.progMode.gameStateL.gameGoaliesRecorded `shouldBe` False
context "goalie data" $ describe "gameGoaliesRecorded" $
it "should set goaliesRecorded" $ let it ("should be " ++ show grFlag) $
s = progState $ M.fromList [(1, newGoalieStats)] gs^.gameGoaliesRecorded `shouldBe` grFlag
in s^.progMode.gameStateL.gameGoaliesRecorded `shouldBe` True
describe "gameGoalieAssigned" $
it ("should be " ++ show gaFlag) $
gs^.gameGoalieAssigned `shouldBe` gaFlag)
-- label, initial stats, goalies recorded, goalie assigned
[ ( "no goalies", noGoalies, False, False )
, ( "one goalie", oneGoalie, True, True )
, ( "two goalies", twoGoalies, True, False )
]
where
goalies = [joe, bob]
joe = newGoalie 2 "Joe"
bob = newGoalie 3 "Bob"
noGoalies = M.empty
oneGoalie = M.fromList [joeStats]
twoGoalies = M.fromList [joeStats, bobStats]
joeStats = (0, newGoalieStats)
bobStats = (1, newGoalieStats)
recordGoalieStatsSpec :: Spec recordGoalieStatsSpec :: Spec
recordGoalieStatsSpec = describe "recordGoalieStats" $ let recordGoalieStatsSpec = describe "recordGoalieStats" $ let

View File

@@ -312,51 +312,93 @@ editSelectedGoalieSpec = describe "editSelectedGoalie" $ mapM_
goalie' n = newGoalie n "foo" goalie' n = newGoalie n "foo"
addPlayerSpec :: Spec addPlayerSpec :: Spec
addPlayerSpec = describe "addPlayer" $ do addPlayerSpec = describe "addPlayer" $ mapM_
let (\(label, expectation, pm, players) -> context label $
p1 = newPlayer 1 "Joe" "centre" it expectation $ let
p2 = newPlayer 2 "Bob" "defense" ps = newProgState
db = newDatabase
& dbPlayers .~ [p1]
s pm = newProgState
& progMode .~ pm & progMode .~ pm
& database .~ db & database.dbPlayers .~ [joe]
ps' = addPlayer ps
in ps'^.database.dbPlayers `shouldBe` players)
context "data available" $ -- label, expectation, progMode, players
it "should create the player" $ let [ ( "wrong mode", failure, MainMenu, [joe] )
s' = addPlayer $ s $ CreatePlayer $ newCreatePlayerState , ( "missing number", failure, noNum, [joe] )
& cpsNumber ?~ 2 , ( "missing rookie flag", failure, noRookie, [joe] )
, ( "missing active flag", failure, noActive, [joe] )
, ( "rookie", success, mkRookie, [joe, rookie] )
, ( "retired", success, mkRetired, [joe, retired] )
, ( "normal player", success, mkNormal, [joe, normal] )
]
where
failure = "should not create the player"
success = "should create the player"
noNum = mkpm Nothing (Just False) (Just True)
noRookie = mkpm (Just 3) Nothing (Just True)
noActive = mkpm (Just 3) (Just False) Nothing
mkRookie = mkpm (Just 3) (Just True) (Just True)
mkRetired = mkpm (Just 3) (Just False) (Just False)
mkNormal = mkpm (Just 3) (Just False) (Just True)
joe = newPlayer 2 "Joe" "centre"
rookie = player True True
retired = player False False
normal = player False True
player r a = newPlayer 3 "Bob" "defense"
& pRookie .~ r
& pActive .~ a
mkpm n r a = CreatePlayer $ newCreatePlayerState
& cpsNumber .~ n
& cpsName .~ "Bob" & cpsName .~ "Bob"
& cpsPosition .~ "defense" & cpsPosition .~ "defense"
in s'^.database.dbPlayers `shouldBe` [p1, p2] & cpsRookieFlag .~ r
& cpsActiveFlag .~ a
context "data unavailable" $
it "should not create the player" $ let
s' = addPlayer $ s MainMenu
in s'^.database.dbPlayers `shouldBe` [p1]
addGoalieSpec :: Spec addGoalieSpec :: Spec
addGoalieSpec = describe "addGoalie" $ do addGoalieSpec = describe "addGoalie" $ mapM_
let (\(label, expectation, pm, goalies) -> context label $
g1 = newGoalie 2 "Joe" it expectation $ let
g2 = newGoalie 3 "Bob" ps = newProgState
db = newDatabase
& dbGoalies .~ [g1]
s pm = newProgState
& database .~ db
& progMode .~ pm & progMode .~ pm
& database.dbGoalies .~ [joe]
ps' = addGoalie ps
in ps'^.database.dbGoalies `shouldBe` goalies)
context "data available" $ -- label, expectation, progMode, expected goalies
it "should create the goalie" $ let [ ( "wrong mode", failure, MainMenu, [joe] )
s' = addGoalie $ s $ CreateGoalie $ newCreateGoalieState , ( "no number", failure, noNum, [joe] )
& cgsNumber ?~ 3 , ( "no rookie flag", failure, noRookie, [joe] )
, ( "no active flag", failure, noActive, [joe] )
, ( "rookie", success, mkRookie, [joe, rookie] )
, ( "retired", success, mkRetired, [joe, retired] )
, ( "normal goalie", success, mkNormal, [joe, normal] )
]
where
failure = "should not create the goalie"
success = "should create the goalie"
noNum = cgs Nothing (Just False) (Just True)
noRookie = cgs (Just 3) Nothing (Just True)
noActive = cgs (Just 3) (Just False) Nothing
mkRookie = cgs (Just 3) (Just True) (Just True)
mkRetired = cgs (Just 3) (Just False) (Just False)
mkNormal = cgs (Just 3) (Just False) (Just True)
joe = newGoalie 2 "Joe"
rookie = goalie True True
retired = goalie False False
normal = goalie False True
goalie r a = newGoalie 3 "Bob"
& gRookie .~ r
& gActive .~ a
cgs n r a = CreateGoalie $ newCreateGoalieState
& cgsNumber .~ n
& cgsName .~ "Bob" & cgsName .~ "Bob"
in s'^.database.dbGoalies `shouldBe` [g1, g2] & cgsRookieFlag .~ r
& cgsActiveFlag .~ a
context "data unavailable" $
it "should not create the goalie" $ let
s' = addGoalie $ s MainMenu
in s'^.database.dbGoalies `shouldBe` [g1]
resetCreatePlayerStateSpec :: Spec resetCreatePlayerStateSpec :: Spec
resetCreatePlayerStateSpec = describe "resetCreatePlayerState" $ let resetCreatePlayerStateSpec = describe "resetCreatePlayerState" $ let

View File

@@ -0,0 +1,79 @@
{-
mtlstats
Copyright (C) 1984, 1985, 2019, 2020 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 Helpers.PositionSpec (spec) where
import Lens.Micro ((&), (.~))
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Helpers.Position
import Mtlstats.Types
spec :: Spec
spec = describe "Position" $ do
posSearchSpec
posSearchExactSpec
getPositionsSpec
posSearchSpec :: Spec
posSearchSpec = describe "posSearch" $ mapM_
(\(sStr, expected) -> context ("search string: " ++ show sStr) $
it ("should be " ++ show expected) $
posSearch sStr db `shouldBe` expected)
[ ( "fOo"
, [ ( 2, "foo" )
]
)
, ( "A"
, [ ( 0, "bar" )
, ( 1, "baz" )
]
)
]
posSearchExactSpec :: Spec
posSearchExactSpec = describe "posSearchExact" $ mapM_
(\(input, expected) -> context ("input: " ++ show input) $
it ("should be " ++ show expected) $
posSearchExact input db `shouldBe` expected)
-- input, expected
[ ( "foo", Just 2 )
, ( "FOO", Nothing )
, ( "bar", Just 0 )
, ( "baz", Just 1 )
, ( "a", Nothing )
, ( "quux", Nothing )
]
getPositionsSpec :: Spec
getPositionsSpec = describe "getPositions" $ let
expected = ["bar", "baz", "foo"]
in it ("should be " ++ show expected) $
getPositions db `shouldBe` expected
db :: Database
db = newDatabase & dbPlayers .~
[ newPlayer 2 "Joe" "foo"
, newPlayer 3 "Bob" "bar"
, newPlayer 5 "Bill" "foo"
, newPlayer 8 "Ed" "baz"
]

View File

@@ -25,8 +25,10 @@ import Test.Hspec (Spec, describe)
import qualified Helpers.GoalieSpec as Goalie import qualified Helpers.GoalieSpec as Goalie
import qualified Helpers.PlayerSpec as Player import qualified Helpers.PlayerSpec as Player
import qualified Helpers.PositionSpec as Position
spec :: Spec spec :: Spec
spec = describe "Helper" $ do spec = describe "Helper" $ do
Player.spec Player.spec
Goalie.spec Goalie.spec
Position.spec