12 Commits

Author SHA1 Message Date
Jonathan Lamothe
1e0b72fc40 version 0.16.0 2020-04-15 22:26:33 -04:00
Jonathan Lamothe
2c5b4a0791 Merge pull request #85 from mtlstats/month-numbers
enter months by number
2020-04-15 22:24:14 -04:00
Jonathan Lamothe
bce31d059b enter months by number 2020-04-15 22:07:56 -04:00
Jonathan Lamothe
99baebe144 version 0.15.2 2020-04-07 21:34:05 -04:00
Jonathan Lamothe
eb3714c40a Merge pull request #84 from mtlstats/allow-ties
allow ties
2020-04-07 21:32:49 -04:00
Jonathan Lamothe
1bd3ae9564 allow ties 2020-04-07 21:30:47 -04:00
Jonathan Lamothe
2adfe9b016 version 0.15.1 2020-04-06 15:34:10 -04:00
Jonathan Lamothe
85a8e3baf1 Merge pull request #83 from mtlstats/active-player-search
only search for active players/goalies on game input
2020-04-06 15:32:29 -04:00
Jonathan Lamothe
393a2c6dc4 updated change log 2020-04-06 15:16:27 -04:00
Jonathan Lamothe
ed240c6a38 only search through active players/goalies on game input 2020-04-06 15:14:48 -04:00
Jonathan Lamothe
4f147cd5a4 implemented searchActiveGoaliePrompt 2020-04-06 15:01:26 -04:00
Jonathan Lamothe
9b6dfc4be9 implemented selectActivePlayerPrompt 2020-04-06 14:46:30 -04:00
15 changed files with 249 additions and 104 deletions

View File

@@ -1,5 +1,14 @@
# Changelog for mtlstats # Changelog for mtlstats
## 0.16.0
- enter months by number
## 0.15.2
- allow ties
## 0.15.1
- only search for active players/goalies on game data input
## 0.15.0 ## 0.15.0
- Ask for database to load on start-up - Ask for database to load on start-up
- Add page break to report file - Add page break to report file

View File

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

View File

@@ -43,9 +43,7 @@ import Mtlstats.Util
overtimeCheck :: ProgState -> ProgState overtimeCheck :: ProgState -> ProgState
overtimeCheck s overtimeCheck s
| fromMaybe False $ gameTied $ s^.progMode.gameStateL = | fromMaybe False $ gameTied $ s^.progMode.gameStateL =
s & progMode.gameStateL s & progMode.gameStateL.overtimeFlag ?~ True
%~ (homeScore .~ Nothing)
. (awayScore .~ Nothing)
| fromMaybe False $ gameWon $ s^.progMode.gameStateL = | fromMaybe False $ gameWon $ s^.progMode.gameStateL =
s & progMode.gameStateL.overtimeFlag ?~ False s & progMode.gameStateL.overtimeFlag ?~ False
| otherwise = s | otherwise = s

View File

@@ -62,7 +62,7 @@ gameYearC :: Controller
gameYearC = promptControllerWith header gameYearPrompt gameYearC = promptControllerWith header gameYearPrompt
gameMonthC :: Controller gameMonthC :: Controller
gameMonthC = menuControllerWith header gameMonthMenu gameMonthC = promptControllerWith monthHeader gameMonthPrompt
gameDayC :: Controller gameDayC :: Controller
gameDayC = promptControllerWith header gameDayPrompt gameDayC = promptControllerWith header gameDayPrompt
@@ -226,6 +226,31 @@ header :: ProgState -> C.Update ()
header s = C.drawString $ header s = C.drawString $
"*** GAME " ++ padNum 2 (s^.database.dbGames) ++ " ***\n" "*** GAME " ++ padNum 2 (s^.database.dbGames) ++ " ***\n"
monthHeader :: ProgState -> C.Update ()
monthHeader s = do
(_, cols) <- C.windowSize
header s
let
table = labelTable $ zip (map show ([1..] :: [Int]))
[ "JANUARY"
, "FEBRUARY"
, "MARCH"
, "APRIL"
, "MAY"
, "JUNE"
, "JULY"
, "AUGUST"
, "SEPTEMBER"
, "OCTOBER"
, "NOVEMBER"
, "DECEMBER"
]
C.drawString $ unlines $
map (centre $ fromIntegral $ pred cols) $
["MONTH:", ""] ++ table ++ [""]
gameGoal :: ProgState -> (Int, Int) gameGoal :: ProgState -> (Int, Int)
gameGoal s = gameGoal s =
( s^.database.dbGames ( s^.database.dbGames

View File

@@ -129,9 +129,14 @@ month _ = ""
labelTable :: [(String, String)] -> [String] labelTable :: [(String, String)] -> [String]
labelTable xs = let labelTable xs = let
labelWidth = maximum $ map (length . fst) xs labelWidth = maximum $ map (length . fst) xs
valWidth = maximum $ map (length . snd) xs
in map in map
(\(label, val) -> right labelWidth label ++ ": " ++ val) ( \(label, val)
xs -> right labelWidth label
++ ": "
++ left valWidth val
) xs
-- | Creates a variable column table of numbers with two axes -- | Creates a variable column table of numbers with two axes
numTable numTable

View File

@@ -29,7 +29,6 @@ module Mtlstats.Menu (
-- * Menus -- * Menus
mainMenu, mainMenu,
newSeasonMenu, newSeasonMenu,
gameMonthMenu,
gameTypeMenu, gameTypeMenu,
gameGoalieMenu, gameGoalieMenu,
editMenu editMenu
@@ -130,26 +129,6 @@ newSeasonMenu = Menu "SEASON TYPE" ()
. startNewGame . startNewGame
] ]
-- | Requests the month in which the game took place
gameMonthMenu :: Menu ()
gameMonthMenu = Menu "MONTH:" () $ map
(\(ch, name, val) ->
MenuItem ch name $
modify $ progMode.gameStateL.gameMonth ?~ val)
[ ( 'A', "JANUARY", 1 )
, ( 'B', "FEBRUARY", 2 )
, ( 'C', "MARCH", 3 )
, ( 'D', "APRIL", 4 )
, ( 'E', "MAY", 5 )
, ( 'F', "JUNE", 6 )
, ( 'G', "JULY", 7 )
, ( 'H', "AUGUST", 8 )
, ( 'I', "SEPTEMBER", 9 )
, ( 'J', "OCTOBER", 10 )
, ( 'K', "NOVEMBER", 11 )
, ( 'L', "DECEMBER", 12 )
]
-- | The game type menu (home/away) -- | The game type menu (home/away)
gameTypeMenu :: Menu () gameTypeMenu :: Menu ()
gameTypeMenu = Menu "GAME TYPE:" () gameTypeMenu = Menu "GAME TYPE:" ()

View File

@@ -31,6 +31,7 @@ module Mtlstats.Prompt (
ucStrPrompt, ucStrPrompt,
namePrompt, namePrompt,
numPrompt, numPrompt,
numPromptRange,
numPromptWithFallback, numPromptWithFallback,
dbNamePrompt, dbNamePrompt,
selectPrompt, selectPrompt,
@@ -43,7 +44,9 @@ module Mtlstats.Prompt (
goalieNumPrompt, goalieNumPrompt,
goalieNamePrompt, goalieNamePrompt,
selectPlayerPrompt, selectPlayerPrompt,
selectActivePlayerPrompt,
selectGoaliePrompt, selectGoaliePrompt,
selectActiveGoaliePrompt,
selectPositionPrompt, selectPositionPrompt,
playerToEditPrompt playerToEditPrompt
) where ) where
@@ -152,6 +155,20 @@ numPrompt
-> Prompt -> Prompt
numPrompt pStr = numPromptWithFallback pStr $ return () numPrompt pStr = numPromptWithFallback pStr $ return ()
-- | Builds a numberic prompt with a range
numPromptRange
:: Int
-- ^ The minimum value
-> Int
-- ^ The maximum value
-> String
-- ^ The prompt string
-> (Int -> Action ())
-- ^ The callback function for the result
-> Prompt
numPromptRange nMin nMax pStr callback = numPrompt pStr $ \n ->
when (n >= nMin && n <= nMax) $ callback n
-- | Builds a numeric prompt with a fallback action -- | Builds a numeric prompt with a fallback action
numPromptWithFallback numPromptWithFallback
:: String :: String
@@ -263,18 +280,21 @@ goalieNamePrompt :: Prompt
goalieNamePrompt = namePrompt "Goalie name: " $ goalieNamePrompt = namePrompt "Goalie name: " $
modify . (progMode.createGoalieStateL.cgsName .~) modify . (progMode.createGoalieStateL.cgsName .~)
-- | Selects a player (creating one if necessary) -- | Selects a player using a specified search function (creating the
selectPlayerPrompt -- player if necessary)
:: String selectPlayerPromptWith
:: (String -> [Player] -> [(Int, Player)])
-- ^ The search function
-> String
-- ^ The prompt string -- ^ The prompt string
-> (Maybe Int -> Action ()) -> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the payer as -- ^ The callback to run (takes the index number of the payer as
-- input) -- input)
-> Prompt -> Prompt
selectPlayerPrompt pStr callback = selectPrompt SelectParams selectPlayerPromptWith sFunc pStr callback = selectPrompt SelectParams
{ spPrompt = pStr { spPrompt = pStr
, spSearchHeader = "Player select:" , spSearchHeader = "Player select:"
, spSearch = \sStr db -> playerSearch sStr (db^.dbPlayers) , spSearch = \sStr db -> sFunc sStr (db^.dbPlayers)
, spSearchExact = \sStr db -> fst <$> playerSearchExact sStr (db^.dbPlayers) , spSearchExact = \sStr db -> fst <$> playerSearchExact sStr (db^.dbPlayers)
, spElemDesc = playerSummary , spElemDesc = playerSummary
, spProcessChar = capitalizeName , spProcessChar = capitalizeName
@@ -292,18 +312,41 @@ selectPlayerPrompt pStr callback = selectPrompt SelectParams
modify $ progMode .~ CreatePlayer cps modify $ progMode .~ CreatePlayer cps
} }
-- | Selects a goalie (creating one if necessary) -- | Selects a player (creating one if necessary)
selectGoaliePrompt selectPlayerPrompt
:: String :: String
-- ^ The prompt string -- ^ The prompt string
-> (Maybe Int -> Action ()) -> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the payer as
-- input)
-> Prompt
selectPlayerPrompt = selectPlayerPromptWith playerSearch
-- | Selects an active player (creating one if necessary)
selectActivePlayerPrompt
:: String
-- ^ The prompt string
-> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the payer as
-- input)
-> Prompt
selectActivePlayerPrompt = selectPlayerPromptWith activePlayerSearch
-- | Selects a goalie with a specified search criteria (creating the
-- goalie if necessary)
selectGoaliePromptWith
:: (String -> [Goalie] -> [(Int, Goalie)])
-- ^ The search criteria
-> String
-- ^ The prompt string
-> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the goalie as -- ^ The callback to run (takes the index number of the goalie as
-- input) -- input)
-> Prompt -> Prompt
selectGoaliePrompt pStr callback = selectPrompt SelectParams selectGoaliePromptWith criteria pStr callback = selectPrompt SelectParams
{ spPrompt = pStr { spPrompt = pStr
, spSearchHeader = "Goalie select:" , spSearchHeader = "Goalie select:"
, spSearch = \sStr db -> goalieSearch sStr (db^.dbGoalies) , spSearch = \sStr db -> criteria sStr (db^.dbGoalies)
, spSearchExact = \sStr db -> fst <$> goalieSearchExact sStr (db^.dbGoalies) , spSearchExact = \sStr db -> fst <$> goalieSearchExact sStr (db^.dbGoalies)
, spElemDesc = goalieSummary , spElemDesc = goalieSummary
, spProcessChar = capitalizeName , spProcessChar = capitalizeName
@@ -321,6 +364,26 @@ selectGoaliePrompt pStr callback = selectPrompt SelectParams
modify $ progMode .~ CreateGoalie cgs modify $ progMode .~ CreateGoalie cgs
} }
-- | Selects a goalie (creating one if necessary)
selectGoaliePrompt
:: String
-- ^ The prompt string
-> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the goalie as
-- input)
-> Prompt
selectGoaliePrompt = selectGoaliePromptWith goalieSearch
-- | Selects an active goalie (creating one if necessary)
selectActiveGoaliePrompt
:: String
-- ^ The prompt string
-> (Maybe Int -> Action ())
-- ^ The callback to run (takes the index number of the goalie as
-- input)
-> Prompt
selectActiveGoaliePrompt = selectGoaliePromptWith activeGoalieSearch
-- | Selects (or creates) a player position -- | Selects (or creates) a player position
selectPositionPrompt selectPositionPrompt
:: String :: String

View File

@@ -23,6 +23,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Prompt.NewGame module Mtlstats.Prompt.NewGame
( gameYearPrompt ( gameYearPrompt
, gameMonthPrompt
, gameDayPrompt , gameDayPrompt
, otherTeamPrompt , otherTeamPrompt
, homeScorePrompt , homeScorePrompt
@@ -48,6 +49,11 @@ gameYearPrompt :: Prompt
gameYearPrompt = numPrompt "Game year: " $ gameYearPrompt = numPrompt "Game year: " $
modify . (progMode.gameStateL.gameYear ?~) modify . (progMode.gameStateL.gameYear ?~)
-- | Prompts for the game month
gameMonthPrompt :: Prompt
gameMonthPrompt = numPromptRange 1 12 "Game month: " $
modify . (progMode.gameStateL.gameMonth ?~)
-- | Prompts for the day of the month the game took place -- | Prompts for the day of the month the game took place
gameDayPrompt :: Prompt gameDayPrompt :: Prompt
gameDayPrompt = numPrompt "Day of month: " $ gameDayPrompt = numPrompt "Day of month: " $
@@ -76,7 +82,7 @@ recordGoalPrompt
-> Int -> Int
-- ^ The goal number -- ^ The goal number
-> Prompt -> Prompt
recordGoalPrompt game goal = selectPlayerPrompt recordGoalPrompt game goal = selectActivePlayerPrompt
( "*** GAME " ++ padNum 2 game ++ " ***\n" ( "*** GAME " ++ padNum 2 game ++ " ***\n"
++ "Who scored goal number " ++ show goal ++ "? " ++ "Who scored goal number " ++ show goal ++ "? "
) $ modify . (progMode.gameStateL.goalBy .~) ) $ modify . (progMode.gameStateL.goalBy .~)
@@ -90,7 +96,7 @@ recordAssistPrompt
-> Int -> Int
-- ^ The assist number -- ^ The assist number
-> Prompt -> Prompt
recordAssistPrompt game goal assist = selectPlayerPrompt recordAssistPrompt game goal assist = selectActivePlayerPrompt
( "*** GAME " ++ padNum 2 game ++ " ***\n" ( "*** GAME " ++ padNum 2 game ++ " ***\n"
++ "Goal: " ++ show goal ++ "\n" ++ "Goal: " ++ show goal ++ "\n"
++ "Assist #" ++ show assist ++ ": " ++ "Assist #" ++ show assist ++ ": "
@@ -104,7 +110,7 @@ recordAssistPrompt game goal assist = selectPlayerPrompt
-- | Prompts for the player to assign penalty minutes to -- | Prompts for the player to assign penalty minutes to
pMinPlayerPrompt :: Prompt pMinPlayerPrompt :: Prompt
pMinPlayerPrompt = selectPlayerPrompt pMinPlayerPrompt = selectActivePlayerPrompt
"Assign penalty minutes to: " $ "Assign penalty minutes to: " $
\case \case
Nothing -> modify $ progMode.gameStateL.gamePMinsRecorded .~ True Nothing -> modify $ progMode.gameStateL.gamePMinsRecorded .~ True

View File

@@ -36,7 +36,8 @@ import Mtlstats.Types
-- | Prompts for a goalie who played in the game -- | Prompts for a goalie who played in the game
selectGameGoaliePrompt :: Prompt selectGameGoaliePrompt :: Prompt
selectGameGoaliePrompt = selectGoaliePrompt "Which goalie played this game: " $ selectGameGoaliePrompt = selectActiveGoaliePrompt
"Which goalie played this game: " $
\case \case
Nothing -> modify finishGoalieEntry Nothing -> modify finishGoalieEntry
Just n -> modify $ progMode.gameStateL.gameSelectedGoalie ?~ n Just n -> modify $ progMode.gameStateL.gameSelectedGoalie ?~ n

View File

@@ -176,6 +176,7 @@ module Mtlstats.Types (
addGameStats, addGameStats,
-- ** Player Helpers -- ** Player Helpers
playerSearch, playerSearch,
activePlayerSearch,
playerSearchExact, playerSearchExact,
modifyPlayer, modifyPlayer,
playerSummary, playerSummary,
@@ -185,6 +186,7 @@ module Mtlstats.Types (
addPlayerStats, addPlayerStats,
-- ** Goalie Helpers -- ** Goalie Helpers
goalieSearch, goalieSearch,
activeGoalieSearch,
goalieSearchExact, goalieSearchExact,
goalieSummary, goalieSummary,
goalieIsActive, goalieIsActive,
@@ -1003,6 +1005,23 @@ addGameStats s1 s2 = GameStats
, _gmsGoalsAgainst = s1^.gmsGoalsAgainst + s2^.gmsGoalsAgainst , _gmsGoalsAgainst = s1^.gmsGoalsAgainst + s2^.gmsGoalsAgainst
} }
-- | Searches through a list of players with a specified criteria
playerSearchWith
:: (Player -> Bool)
-- ^ The search criteria
-> String
-- ^ The search string
-> [Player]
-- ^ The list of players to search
-> [(Int, Player)]
-- ^ The matching players with their index numbers
playerSearchWith criteria sStr =
filter match . zip [0..]
where
match (_, p)
= map toUpper sStr `isInfixOf` map toUpper (p^.pName)
&& criteria p
-- | Searches through a list of players -- | Searches through a list of players
playerSearch playerSearch
:: String :: String
@@ -1011,9 +1030,17 @@ playerSearch
-- ^ The list of players to search -- ^ The list of players to search
-> [(Int, Player)] -> [(Int, Player)]
-- ^ The matching players with their index numbers -- ^ The matching players with their index numbers
playerSearch sStr = playerSearch = playerSearchWith $ const True
filter match . zip [0..]
where match (_, p) = map toUpper sStr `isInfixOf` map toUpper (p^.pName) -- | Searches through a list of players for an active player
activePlayerSearch
:: String
-- ^ The search string
-> [Player]
-- ^ The list of players to search
-> [(Int, Player)]
-- ^ The matching players with their index numbers
activePlayerSearch = playerSearchWith (^.pActive)
-- | Searches for a player by exact match on name -- | Searches for a player by exact match on name
playerSearchExact playerSearchExact
@@ -1068,6 +1095,23 @@ addPlayerStats s1 s2 = newPlayerStats
& psAssists .~ s1^.psAssists + s2^.psAssists & psAssists .~ s1^.psAssists + s2^.psAssists
& psPMin .~ s1^.psPMin + s2^.psPMin & psPMin .~ s1^.psPMin + s2^.psPMin
-- | Searches a list of goalies with a search criteria
goalieSearchWith
:: (Goalie -> Bool)
-- ^ The search criteria
-> String
-- ^ The search string
-> [Goalie]
-- ^ The list to search
-> [(Int, Goalie)]
-- ^ The search results with their corresponding index numbers
goalieSearchWith criteria sStr =
filter match . zip [0..]
where
match (_, g)
= map toUpper sStr `isInfixOf` map toUpper (g^.gName)
&& criteria g
-- | Searches a list of goalies -- | Searches a list of goalies
goalieSearch goalieSearch
:: String :: String
@@ -1076,9 +1120,17 @@ goalieSearch
-- ^ The list to search -- ^ The list to search
-> [(Int, Goalie)] -> [(Int, Goalie)]
-- ^ The search results with their corresponding index numbers -- ^ The search results with their corresponding index numbers
goalieSearch sStr = goalieSearch = goalieSearchWith $ const True
filter match . zip [0..]
where match (_, g) = map toUpper sStr `isInfixOf` map toUpper (g^.gName) -- | Searches a list of goalies for an active goalie
activeGoalieSearch
:: String
-- ^ The search string
-> [Goalie]
-- ^ The list to search
-> [(Int, Goalie)]
-- ^ The search results with their corresponding index numbers
activeGoalieSearch = goalieSearchWith (^.gActive)
-- | Searches a list of goalies for an exact match -- | Searches a list of goalies for an exact match
goalieSearchExact goalieSearchExact

View File

@@ -48,61 +48,31 @@ spec = describe "NewGame" $ do
GoalieInput.spec GoalieInput.spec
overtimeCheckSpec :: Spec overtimeCheckSpec :: Spec
overtimeCheckSpec = describe "overtimeCheck" $ do overtimeCheckSpec = describe "overtimeCheck" $ mapM_
(\(label, expectation, gt, home, away, otf) ->
context label $
it expectation $ let
ps = newProgState & progMode.gameStateL
%~ (gameType ?~ gt)
. (homeScore ?~ home)
. (awayScore ?~ away)
context "tie game" $ do ps' = overtimeCheck ps
let in ps'^.progMode.gameStateL.overtimeFlag `shouldBe` otf)
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 1)
. (awayScore ?~ 1)
& overtimeCheck
it "should clear the home score" $ -- label, expectation, type, home, away, ot flag
s^.progMode.gameStateL.homeScore `shouldBe` Nothing [ ( "home win", clearFlag, HomeGame, 2, 1, Just False )
, ( "home loss", leaveFlag, HomeGame, 1, 2, Nothing )
, ( "home tie", setFlag, HomeGame, 1, 1, Just True )
, ( "away win", clearFlag, AwayGame, 1, 2, Just False )
, ( "away loss", leaveFlag, AwayGame, 2, 1, Nothing )
, ( "away tie", setFlag, AwayGame, 1, 1, Just True )
]
it "should clear the away score" $ where
s^.progMode.gameStateL.awayScore `shouldBe` Nothing clearFlag = "should set the overtimeFlag to True"
setFlag = "should set the overtimeFlag to False"
it "should leave the overtimeFlag blank" $ leaveFlag = "should leave the overtimeFlag as Nothing"
s^.progMode.gameStateL.overtimeFlag `shouldBe` Nothing
context "game won" $ do
let
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 2)
. (awayScore ?~ 1)
& overtimeCheck
it "should not change the home score" $
s^.progMode.gameStateL.homeScore `shouldBe` Just 2
it "should not change the away score" $
s^.progMode.gameStateL.awayScore `shouldBe` Just 1
it "should set the overtimeCheck flag to False" $
s^.progMode.gameStateL.overtimeFlag `shouldBe` Just False
context "game lost" $ do
let
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 1)
. (awayScore ?~ 2)
& overtimeCheck
it "should not change the home score" $
s^.progMode.gameStateL.homeScore `shouldBe` Just 1
it "should not change the away score" $
s^.progMode.gameStateL.awayScore `shouldBe` Just 2
it "should leave the overtimeCheck flag blank" $
s^.progMode.gameStateL.overtimeFlag `shouldBe` Nothing
updateGameStatsSpec :: Spec updateGameStatsSpec :: Spec
updateGameStatsSpec = describe "updateGameStats" $ do updateGameStatsSpec = describe "updateGameStats" $ do

View File

@@ -141,9 +141,9 @@ labelTableSpec = describe "labelTable" $
] ]
expected = expected =
[ " foo: bar" [ " foo: bar "
, " baz: quux" , " baz: quux"
, "longer: x" , "longer: x "
] ]
in labelTable input `shouldBe` expected in labelTable input `shouldBe` expected

View File

@@ -54,7 +54,7 @@ goalieDetailsSpec = describe "goalieDetails" $ let
. ( gsTies .~ 15 ) . ( gsTies .~ 15 )
expected = unlines expected = unlines
[ "Number: 1" [ "Number: 1 "
, " Name: Joe*" , " Name: Joe*"
, "" , ""
, " YTD Lifetime" , " YTD Lifetime"

View File

@@ -50,8 +50,8 @@ playerDetailsSpec = describe "playerDetails" $
} }
expected = unlines expected = unlines
[ " Number: 1" [ " Number: 1 "
, " Name: Joe*" , " Name: Joe* "
, "Position: centre" , "Position: centre"
, "" , ""
, " YTD Lifetime" , " YTD Lifetime"

View File

@@ -73,6 +73,7 @@ spec = describe "Mtlstats.Types" $ do
gmsPointsSpec gmsPointsSpec
addGameStatsSpec addGameStatsSpec
playerSearchSpec playerSearchSpec
activePlayerSearchSpec
playerSearchExactSpec playerSearchExactSpec
modifyPlayerSpec modifyPlayerSpec
playerSummarySpec playerSummarySpec
@@ -80,6 +81,7 @@ spec = describe "Mtlstats.Types" $ do
psPointsSpec psPointsSpec
addPlayerStatsSpec addPlayerStatsSpec
goalieSearchSpec goalieSearchSpec
activeGoalieSearchSpec
goalieSearchExactSpec goalieSearchExactSpec
goalieSummarySpec goalieSummarySpec
goalieIsActiveSpec goalieIsActiveSpec
@@ -647,6 +649,19 @@ playerSearchSpec = describe "playerSearch" $ mapM_
, ( "x", [] ) , ( "x", [] )
] ]
activePlayerSearchSpec :: Spec
activePlayerSearchSpec = describe "activePlayerSearch" $ mapM_
(\(sStr, expected) -> context sStr $
it ("should return " ++ show expected) $ let
ps = [joe, bob, steve & pActive .~ False]
in activePlayerSearch sStr ps `shouldBe` expected)
-- search, result
[ ( "joe", [(0, joe)] )
, ( "o", [(0, joe), (1, bob)] )
, ( "e", [(0, joe)] )
, ( "x", [] )
]
playerSearchExactSpec :: Spec playerSearchExactSpec :: Spec
playerSearchExactSpec = describe "playerSearchExact" $ mapM_ playerSearchExactSpec = describe "playerSearchExact" $ mapM_
(\(sStr, expected) -> context sStr $ (\(sStr, expected) -> context sStr $
@@ -778,6 +793,28 @@ goalieSearchSpec = describe "goalieSearch" $ do
it "should return Bob" $ it "should return Bob" $
goalieSearch "bob" goalies `shouldBe` [result 1] goalieSearch "bob" goalies `shouldBe` [result 1]
activeGoalieSearchSpec :: Spec
activeGoalieSearchSpec = describe "activeGoalieSearch" $ do
let
goalies =
[ newGoalie 2 "Joe"
, newGoalie 3 "Bob"
, newGoalie 5 "Steve" & gActive .~ False
]
result n = (n, goalies!!n)
context "partial match" $
it "should return Joe" $
activeGoalieSearch "e" goalies `shouldBe` [result 0]
context "no match" $
it "should return an empty list" $
activeGoalieSearch "x" goalies `shouldBe` []
context "exact match" $
it "should return Bob" $
activeGoalieSearch "bob" goalies `shouldBe` [result 1]
goalieSearchExactSpec :: Spec goalieSearchExactSpec :: Spec
goalieSearchExactSpec = describe "goalieSearchExact" $ do goalieSearchExactSpec = describe "goalieSearchExact" $ do
let let