diff --git a/ChangeLog.md b/ChangeLog.md index 32a2ae0..2ef4d51 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -1,5 +1,8 @@ # Changelog for mtlstats +## current +- Shortened views to fit within 25 lines + ## 0.6.0 - Generate lifetime statistics report - Implemented goalie editing diff --git a/src/Mtlstats/Control/EditGoalie.hs b/src/Mtlstats/Control/EditGoalie.hs index 094ac09..10fa61a 100644 --- a/src/Mtlstats/Control/EditGoalie.hs +++ b/src/Mtlstats/Control/EditGoalie.hs @@ -27,6 +27,7 @@ import Data.Maybe (fromMaybe) import Lens.Micro ((^.)) import UI.NCurses as C +import Mtlstats.Helpers.Goalie import Mtlstats.Menu import Mtlstats.Menu.EditGoalie import Mtlstats.Prompt @@ -118,20 +119,4 @@ 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) - , "" - ] + Just $ goalieDetails g ++ "\n" diff --git a/src/Mtlstats/Control/EditPlayer.hs b/src/Mtlstats/Control/EditPlayer.hs index 8c7b65d..1aeb464 100644 --- a/src/Mtlstats/Control/EditPlayer.hs +++ b/src/Mtlstats/Control/EditPlayer.hs @@ -25,7 +25,9 @@ import Data.Maybe (fromMaybe) import Lens.Micro ((^.)) import qualified UI.NCurses as C +import Mtlstats.Helpers.Player import Mtlstats.Menu +import Mtlstats.Menu.EditPlayer import Mtlstats.Prompt import Mtlstats.Prompt.EditPlayer import Mtlstats.Types @@ -40,6 +42,8 @@ editPlayerC eps EPNumber -> numberC EPName -> nameC EPPosition -> positionC + EPYtd -> ytdC + EPLifetime -> lifetimeC EPYtdGoals -> ytdGoalsC EPYtdAssists -> ytdAssistsC EPYtdPMin -> ytdPMinC @@ -48,96 +52,46 @@ editPlayerC eps EPLtPMin -> ltPMinC selectPlayerC :: Controller -selectPlayerC = Controller - { drawController = drawPrompt playerToEditPrompt - , handleController = \e -> do - promptHandler playerToEditPrompt e - return True - } +selectPlayerC = promptController playerToEditPrompt menuC :: Controller -menuC = Controller - { drawController = \s -> do - let - header = fromMaybe "" $ do - pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer - p <- nth pid $ s^.database.dbPlayers - Just $ playerDetails p ++ "\n" - C.drawString header - drawMenu editPlayerMenu - , handleController = \e -> do - menuHandler editPlayerMenu e - return True - } +menuC = menuControllerWith header editPlayerMenu numberC :: Controller -numberC = Controller - { drawController = drawPrompt editPlayerNumPrompt - , handleController = \e -> do - promptHandler editPlayerNumPrompt e - return True - } +numberC = promptController editPlayerNumPrompt nameC :: Controller -nameC = Controller - { drawController = drawPrompt editPlayerNamePrompt - , handleController = \e -> do - promptHandler editPlayerNamePrompt e - return True - } +nameC = promptController editPlayerNamePrompt positionC :: Controller -positionC = Controller - { drawController = drawPrompt editPlayerPosPrompt - , handleController = \e -> do - promptHandler editPlayerPosPrompt e - return True - } +positionC = promptController editPlayerPosPrompt + +ytdC :: Controller +ytdC = menuControllerWith header editPlayerYtdMenu + +lifetimeC :: Controller +lifetimeC = menuControllerWith header editPlayerLtMenu ytdGoalsC :: Controller -ytdGoalsC = Controller - { drawController = drawPrompt editPlayerYtdGoalsPrompt - , handleController = \e -> do - promptHandler editPlayerYtdGoalsPrompt e - return True - } +ytdGoalsC = promptController editPlayerYtdGoalsPrompt ytdAssistsC :: Controller -ytdAssistsC = Controller - { drawController = drawPrompt editPlayerYtdAssistsPrompt - , handleController = \e -> do - promptHandler editPlayerYtdAssistsPrompt e - return True - } +ytdAssistsC = promptController editPlayerYtdAssistsPrompt ytdPMinC :: Controller -ytdPMinC = Controller - { drawController = drawPrompt editPlayerYtdPMinPrompt - , handleController = \e -> do - promptHandler editPlayerYtdPMinPrompt e - return True - } +ytdPMinC = promptController editPlayerYtdPMinPrompt ltGoalsC :: Controller -ltGoalsC = Controller - { drawController = drawPrompt editPlayerLtGoalsPrompt - , handleController = \e -> do - promptHandler editPlayerLtGoalsPrompt e - return True - } +ltGoalsC = promptController editPlayerLtGoalsPrompt ltAssistsC :: Controller -ltAssistsC = Controller - { drawController = drawPrompt editPlayerLtAssistsPrompt - , handleController = \e -> do - promptHandler editPlayerLtAssistsPrompt e - return True - } +ltAssistsC = promptController editPlayerLtAssistsPrompt ltPMinC :: Controller -ltPMinC = Controller - { drawController = drawPrompt editPlayerLtPMinPrompt - , handleController = \e -> do - promptHandler editPlayerLtPMinPrompt e - return True - } +ltPMinC = promptController editPlayerLtPMinPrompt + +header :: ProgState -> C.Update () +header s = C.drawString $ fromMaybe "" $ do + pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer + player <- nth pid $ s^.database.dbPlayers + Just $ playerDetails player ++ "\n" diff --git a/src/Mtlstats/Format.hs b/src/Mtlstats/Format.hs index 8ccd4cc..5dfbcd1 100644 --- a/src/Mtlstats/Format.hs +++ b/src/Mtlstats/Format.hs @@ -26,8 +26,13 @@ module Mtlstats.Format , centre , overlay , month + , labelTable + , numTable + , tableWith ) where +import Data.List (transpose) + -- | Pad an 'Int' with leading zeroes to fit a certain character width padNum :: Int @@ -101,3 +106,44 @@ month 10 = "OCT" month 11 = "NOV" month 12 = "DEC" month _ = "" + +-- | Creates a two-column table with labels +labelTable :: [(String, String)] -> [String] +labelTable xs = let + labelWidth = maximum $ map (length . fst) xs + in map + (\(label, val) -> right labelWidth label ++ ": " ++ val) + xs + +-- | Creates a variable column table of numbers with two axes +numTable + :: [String] + -- ^ The top column labels + -> [(String, [Int])] + -- ^ The rows with their labels + -> [String] +numTable headers rows = tableWith right $ header : body + where + header = "" : headers + body = map + (\(label, row) -> + label : map show row) + rows + +-- | Creates a table from a two-dimensional list with a specified +-- padding function +tableWith + :: (Int -> String -> String) + -- ^ The padding function + -> [[String]] + -- ^ The cells + -> [String] +tableWith func tdata = let + widths = map (map length) tdata + colWidths = map maximum $ transpose widths + fitted = map + (\row -> map + (\(str, len) -> func len str) $ + zip row colWidths) + tdata + in map unwords fitted diff --git a/src/Mtlstats/Helpers/Goalie.hs b/src/Mtlstats/Helpers/Goalie.hs new file mode 100644 index 0000000..0b760ed --- /dev/null +++ b/src/Mtlstats/Helpers/Goalie.hs @@ -0,0 +1,47 @@ +{- | + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module Mtlstats.Helpers.Goalie (goalieDetails) where + +import Lens.Micro ((^.)) + +import Mtlstats.Format +import Mtlstats.Types + +-- | Provides a detailed 'String' describing a 'Goalie' +goalieDetails :: Goalie -> String +goalieDetails g = let + header = unlines $ labelTable + [ ( "Number", show $ g^.gNumber ) + , ( "Name", g^.gName ) + ] + + body = unlines $ numTable ["YTD", "Lifetime"] $ map + (\(label, lens) -> (label, [g^.gYtd.lens, g^.gLifetime.lens])) + [ ( "Games played", gsGames ) + , ( "Mins played", gsMinsPlayed ) + , ( "Goals allowed", gsGoalsAllowed ) + , ( "Wins", gsWins ) + , ( "Losses", gsLosses ) + , ( "Ties", gsTies ) + ] + + in header ++ "\n" ++ body diff --git a/src/Mtlstats/Helpers/Player.hs b/src/Mtlstats/Helpers/Player.hs new file mode 100644 index 0000000..6798109 --- /dev/null +++ b/src/Mtlstats/Helpers/Player.hs @@ -0,0 +1,45 @@ +{- | + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module Mtlstats.Helpers.Player (playerDetails) where + +import Lens.Micro ((^.)) + +import Mtlstats.Format +import Mtlstats.Types + +-- | Provides a detailed string describing a 'Player' +playerDetails :: Player -> String +playerDetails p = unlines $ top ++ [""] ++ table + where + top = labelTable + [ ( "Number", show $ p^.pNumber ) + , ( "Name", p^.pName ) + , ( "Position", p^.pPosition ) + ] + + table = numTable ["YTD", "Lifetime"] $ map + (\(label, lens) -> + (label, [p^.pYtd.lens, p^.pLifetime.lens])) + [ ( "Goals", psGoals ) + , ( "Assists", psAssists ) + , ( "Penalty mins", psPMin ) + ] diff --git a/src/Mtlstats/Menu.hs b/src/Mtlstats/Menu.hs index cfad6b8..db404ae 100644 --- a/src/Mtlstats/Menu.hs +++ b/src/Mtlstats/Menu.hs @@ -30,7 +30,6 @@ module Mtlstats.Menu ( newSeasonMenu, gameMonthMenu, gameTypeMenu, - editPlayerMenu, gameGoalieMenu ) where @@ -40,7 +39,7 @@ import Data.Aeson (encodeFile) import Data.Char (toUpper) import qualified Data.Map as M import Data.Maybe (mapMaybe) -import Lens.Micro ((^.), (.~), (?~)) +import Lens.Micro ((^.), (?~)) import Lens.Micro.Extras (view) import System.EasyFile ( createDirectoryIfMissing @@ -157,24 +156,6 @@ gameTypeMenu = Menu "Game type:" () modify $ progMode.gameStateL.gameType ?~ AwayGame ] --- | The player edit menu -editPlayerMenu :: Menu () -editPlayerMenu = Menu "*** EDIT PLAYER ***" () $ map - (\(ch, label, mode) -> MenuItem ch label $ case mode of - Nothing -> modify $ progMode .~ MainMenu - Just m -> modify $ progMode.editPlayerStateL.epsMode .~ m) - [ ( '1', "Change number", Just EPNumber ) - , ( '2', "Change name", Just EPName ) - , ( '3', "Change position", Just EPPosition ) - , ( '4', "YTD goals", Just EPYtdGoals ) - , ( '5', "YTD assists", Just EPYtdAssists ) - , ( '6', "YTD penalty mins", Just EPYtdPMin ) - , ( '7', "Lifetime goals", Just EPLtGoals ) - , ( '8', "Lifetime assists", Just EPLtAssists ) - , ( '9', "Lifetime penalty mins", Just EPLtPMin ) - , ( '0', "Finished editing", Nothing ) - ] - -- | Game goalie selection menu gameGoalieMenu :: ProgState -> Menu () gameGoalieMenu s = let diff --git a/src/Mtlstats/Menu/EditPlayer.hs b/src/Mtlstats/Menu/EditPlayer.hs new file mode 100644 index 0000000..8167f88 --- /dev/null +++ b/src/Mtlstats/Menu/EditPlayer.hs @@ -0,0 +1,74 @@ +{- | + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module Mtlstats.Menu.EditPlayer + ( editPlayerMenu + , editPlayerYtdMenu + , editPlayerLtMenu + ) where + +import Control.Monad.Trans.State (modify) +import Lens.Micro ((.~)) + +import Mtlstats.Types +import Mtlstats.Types.Menu + +-- | The 'Player' edit menu +editPlayerMenu :: Menu () +editPlayerMenu = Menu "*** EDIT PLAYER ***" () $ map + (\(ch, label, mode) -> MenuItem ch label $ case mode of + Nothing -> modify $ progMode .~ MainMenu + Just m -> modify $ progMode.editPlayerStateL.epsMode .~ m) + -- key, label, value + [ ( '1', "Edit number", Just EPNumber ) + , ( '2', "Edit name", Just EPName ) + , ( '3', "Edit position", Just EPPosition ) + , ( '4', "Edit YTD stats", Just EPYtd ) + , ( '5', "Edit lifetime stats", Just EPLifetime ) + , ( 'R', "Finished editing", Nothing ) + ] + +-- | The 'Player' YTD stats edit menu +editPlayerYtdMenu :: Menu () +editPlayerYtdMenu = editMenu + "*** EDIT PLAYER YEAR-TO-DATE ***" + -- key, label, value + [ ( '1', "Edit YTD goals", EPYtdGoals ) + , ( '2', "Edit YTD assists", EPYtdAssists ) + , ( '3', "Edit YTD penalty mins", EPYtdPMin ) + , ( 'R', "Return to player edit menu", EPMenu ) + ] + +-- | The 'Player' lifetime stats edit menu +editPlayerLtMenu :: Menu () +editPlayerLtMenu = editMenu + "*** EDIT PLAYER LIFETIME ***" + -- key, label, value + [ ( '1', "Edit lifetime goals", EPLtGoals ) + , ( '2', "Edit lifetime assits", EPLtAssists ) + , ( '3', "Edit lifetime penalty mins", EPLtPMin ) + , ( 'R', "Return to edit player menu", EPMenu ) + ] + +editMenu :: String -> [(Char, String, EditPlayerMode)] -> Menu () +editMenu title = Menu title () . map + (\(key, label, val) -> MenuItem key label $ + modify $ progMode.editPlayerStateL.epsMode .~ val) diff --git a/src/Mtlstats/Types.hs b/src/Mtlstats/Types.hs index 5174aca..827e779 100644 --- a/src/Mtlstats/Types.hs +++ b/src/Mtlstats/Types.hs @@ -161,7 +161,6 @@ module Mtlstats.Types ( playerSearchExact, modifyPlayer, playerSummary, - playerDetails, playerIsActive, -- ** PlayerStats Helpers psPoints, @@ -335,6 +334,8 @@ data EditPlayerMode | EPNumber | EPName | EPPosition + | EPYtd + | EPLifetime | EPYtdGoals | EPYtdAssists | EPYtdPMin @@ -915,20 +916,6 @@ playerSummary :: Player -> String playerSummary p = p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition --- | Provides a detailed string describing a 'Player' -playerDetails :: Player -> String -playerDetails p = unlines - [ " Number: " ++ show (p^.pNumber) - , " Name: " ++ p^.pName - , " Position: " ++ p^.pPosition - , " YTD goals: " ++ show (p^.pYtd.psGoals) - , " YTD assists: " ++ show (p^.pYtd.psAssists) - , " YTD penalty mins: " ++ show (p^.pYtd.psPMin) - , " Lifetime goals: " ++ show (p^.pLifetime.psGoals) - , " Lifetime assists: " ++ show (p^.pLifetime.psAssists) - , "Lifetime penalty mins: " ++ show (p^.pLifetime.psPMin) - ] - -- | Determines whether or not a player has been active in the current -- season/year playerIsActive :: Player -> Bool diff --git a/test/FormatSpec.hs b/test/FormatSpec.hs index bcfa781..6c80913 100644 --- a/test/FormatSpec.hs +++ b/test/FormatSpec.hs @@ -33,6 +33,9 @@ spec = describe "Mtlstats.Format" $ do centreSpec overlaySpec monthSpec + labelTableSpec + numTableSpec + tableWithSpec padNumSpec :: Spec padNumSpec = describe "padNum" $ do @@ -111,3 +114,63 @@ monthSpec = describe "month" $ do context "invalid" $ it "should return an empty string" $ month 0 `shouldBe` "" + +labelTableSpec :: Spec +labelTableSpec = describe "labelTable" $ + it "should format the table" $ let + input = + [ ( "foo", "bar" ) + , ( "baz", "quux" ) + , ( "longer", "x" ) + ] + + expected = + [ " foo: bar" + , " baz: quux" + , "longer: x" + ] + + in labelTable input `shouldBe` expected + +numTableSpec :: Spec +numTableSpec = describe "numTable" $ + it "should format the table" $ let + headers = ["foo", "bar", "baz"] + + rows = + [ ( "quux", [ 1, 2, 3 ] ) + , ( "xyzzy", [ 9, 99, 999 ] ) + ] + + expected = + [ " foo bar baz" + , " quux 1 2 3" + , "xyzzy 9 99 999" + ] + + in numTable headers rows `shouldBe` expected + +tableWithSpec :: Spec +tableWithSpec = describe "tableWith" $ let + vals = + [ [ "foo", "bar", "baz" ] + , [ "quux", "xyzzy", "x" ] + ] + + in mapM_ + (\(label, func, expected) -> context label $ + it "should format the table" $ + tableWith func vals `shouldBe` expected) + [ ( "align left" + , left + , [ "foo bar baz" + , "quux xyzzy x " + ] + ) + , ( "align right" + , right + , [ " foo bar baz" + , "quux xyzzy x" + ] + ) + ] diff --git a/test/Helpers/GoalieSpec.hs b/test/Helpers/GoalieSpec.hs new file mode 100644 index 0000000..af8a0c2 --- /dev/null +++ b/test/Helpers/GoalieSpec.hs @@ -0,0 +1,66 @@ +{- + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module Helpers.GoalieSpec (spec) where + +import Lens.Micro ((&), (.~), (%~)) +import Test.Hspec (Spec, describe, it, shouldBe) + +import Mtlstats.Helpers.Goalie +import Mtlstats.Types + +spec :: Spec +spec = describe "Goalie" + goalieDetailsSpec + +goalieDetailsSpec :: Spec +goalieDetailsSpec = describe "goalieDetails" $ let + input = newGoalie 1 "Joe" + & gYtd + %~ ( gsGames .~ 2 ) + . ( gsMinsPlayed .~ 3 ) + . ( gsGoalsAllowed .~ 4 ) + . ( gsWins .~ 5 ) + . ( gsLosses .~ 6 ) + . ( gsTies .~ 7 ) + & gLifetime + %~ ( gsGames .~ 8 ) + . ( gsMinsPlayed .~ 9 ) + . ( gsGoalsAllowed .~ 10 ) + . ( gsWins .~ 11 ) + . ( gsLosses .~ 12 ) + . ( gsTies .~ 13 ) + + expected = unlines + [ "Number: 1" + , " Name: Joe" + , "" + , " YTD Lifetime" + , " Games played 2 8" + , " Mins played 3 9" + , "Goals allowed 4 10" + , " Wins 5 11" + , " Losses 6 12" + , " Ties 7 13" + ] + + in it "should format the output correctly" $ + goalieDetails input `shouldBe` expected diff --git a/test/Helpers/PlayerSpec.hs b/test/Helpers/PlayerSpec.hs new file mode 100644 index 0000000..6bd903a --- /dev/null +++ b/test/Helpers/PlayerSpec.hs @@ -0,0 +1,61 @@ +{- + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module Helpers.PlayerSpec (spec) where + +import Lens.Micro ((&), (.~)) +import Test.Hspec (Spec, describe, it, shouldBe) + +import Mtlstats.Helpers.Player +import Mtlstats.Types + +spec :: Spec +spec = describe "Player" + playerDetailsSpec + +playerDetailsSpec :: Spec +playerDetailsSpec = describe "playerDetails" $ + it "should give a detailed description" $ let + + p = newPlayer 1 "Joe" "centre" + & pYtd .~ PlayerStats + { _psGoals = 2 + , _psAssists = 3 + , _psPMin = 4 + } + & pLifetime .~ PlayerStats + { _psGoals = 5 + , _psAssists = 6 + , _psPMin = 7 + } + + expected = unlines + [ " Number: 1" + , " Name: Joe" + , "Position: centre" + , "" + , " YTD Lifetime" + , " Goals 2 5" + , " Assists 3 6" + , "Penalty mins 4 7" + ] + + in playerDetails p `shouldBe` expected diff --git a/test/HelpersSpec.hs b/test/HelpersSpec.hs new file mode 100644 index 0000000..cfeeaae --- /dev/null +++ b/test/HelpersSpec.hs @@ -0,0 +1,32 @@ +{- + +mtlstats +Copyright (C) 2019 Rhéal Lamothe + + +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 . + +-} + +module HelpersSpec (spec) where + +import Test.Hspec (Spec, describe) + +import qualified Helpers.GoalieSpec as Goalie +import qualified Helpers.PlayerSpec as Player + +spec :: Spec +spec = describe "Helper" $ do + Player.spec + Goalie.spec diff --git a/test/Spec.hs b/test/Spec.hs index 4edf493..9aed37c 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -24,6 +24,7 @@ import Test.Hspec (hspec) import qualified ActionsSpec as Actions import qualified FormatSpec as Format import qualified HandlersSpec as Handlers +import qualified HelpersSpec as Helpers import qualified ReportSpec as Report import qualified TypesSpec as Types import qualified UtilSpec as Util @@ -31,6 +32,7 @@ import qualified UtilSpec as Util main :: IO () main = hspec $ do Types.spec + Helpers.spec Actions.spec Format.spec Handlers.spec diff --git a/test/TypesSpec.hs b/test/TypesSpec.hs index 06b8e2d..60dbcd6 100644 --- a/test/TypesSpec.hs +++ b/test/TypesSpec.hs @@ -72,7 +72,6 @@ spec = describe "Mtlstats.Types" $ do playerSearchExactSpec modifyPlayerSpec playerSummarySpec - playerDetailsSpec playerIsActiveSpec psPointsSpec addPlayerStatsSpec @@ -636,36 +635,6 @@ playerSummarySpec = describe "playerSummary" $ it "should be \"Joe (2) center\"" $ playerSummary joe `shouldBe` "Joe (2) center" -playerDetailsSpec :: Spec -playerDetailsSpec = describe "playerDetails" $ - it "should give a detailed description" $ let - - p = newPlayer 1 "Joe" "centre" - & pYtd .~ PlayerStats - { _psGoals = 2 - , _psAssists = 3 - , _psPMin = 4 - } - & pLifetime .~ PlayerStats - { _psGoals = 5 - , _psAssists = 6 - , _psPMin = 7 - } - - expected = unlines - [ " Number: 1" - , " Name: Joe" - , " Position: centre" - , " YTD goals: 2" - , " YTD assists: 3" - , " YTD penalty mins: 4" - , " Lifetime goals: 5" - , " Lifetime assists: 6" - , "Lifetime penalty mins: 7" - ] - - in playerDetails p `shouldBe` expected - playerIsActiveSpec :: Spec playerIsActiveSpec = describe "playerIsActive" $ do let