Merge pull request #26 from mtlstats/ytd-stats

year-to-date statistics
This commit is contained in:
Jonathan Lamothe 2019-10-16 02:37:50 -04:00 committed by GitHub
commit 569f009dcd
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
9 changed files with 217 additions and 41 deletions

View File

@ -37,6 +37,9 @@ module Mtlstats.Actions
, awardAssist , awardAssist
, resetGoalData , resetGoalData
, assignPMins , assignPMins
, backHome
, scrollUp
, scrollDown
) where ) where
import Control.Monad.Trans.State (modify) import Control.Monad.Trans.State (modify)
@ -229,3 +232,18 @@ assignPMins mins s = fromMaybe s $ do
(psPMin +~ mins) (psPMin +~ mins)
) )
. (selectedPlayer .~ Nothing) . (selectedPlayer .~ Nothing)
-- | Resets the program state back to the main menu
backHome :: ProgState -> ProgState
backHome
= (progMode .~ MainMenu)
. (inputBuffer .~ "")
. (scrollOffset .~ 0)
-- | Scrolls the display up
scrollUp :: ProgState -> ProgState
scrollUp = scrollOffset %~ max 0 . pred
-- | Scrolls the display down
scrollDown :: ProgState -> ProgState
scrollDown = scrollOffset %~ succ

View File

@ -25,7 +25,7 @@ import Control.Monad (join, when)
import Control.Monad.Trans.State (gets, modify) import Control.Monad.Trans.State (gets, modify)
import Data.Char (toUpper) import Data.Char (toUpper)
import Data.Maybe (fromJust, fromMaybe, isJust) import Data.Maybe (fromJust, fromMaybe, isJust)
import Lens.Micro ((^.), (.~)) import Lens.Micro ((^.), (.~), (%~))
import Lens.Micro.Extras (view) import Lens.Micro.Extras (view)
import qualified UI.NCurses as C import qualified UI.NCurses as C
@ -270,16 +270,20 @@ getPMinsC = Controller
reportC :: Controller reportC :: Controller
reportC = Controller reportC = Controller
{ drawController = \s -> do { drawController = \s -> do
(_, cols) <- C.windowSize (rows, cols) <- C.windowSize
C.drawString $ report (fromInteger $ pred cols) s C.drawString $ unlines $ slice
(s^.scrollOffset)
(fromInteger $ pred rows)
(report (fromInteger $ pred cols) s)
return C.CursorInvisible return C.CursorInvisible
, handleController = \e -> do , handleController = \e -> do
when case e of
(case e of C.EventSpecialKey C.KeyUpArrow -> modify scrollUp
C.EventCharacter _ -> True C.EventSpecialKey C.KeyDownArrow -> modify scrollDown
C.EventSpecialKey _ -> True C.EventSpecialKey C.KeyHome -> modify $ scrollOffset .~ 0
_ -> False) $ C.EventSpecialKey _ -> modify backHome
modify $ progMode .~ MainMenu C.EventCharacter _ -> modify backHome
_ -> return ()
return True return True
} }

View File

@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
module Mtlstats.Report (report, gameDate) where module Mtlstats.Report (report, gameDate, playerNameColWidth) where
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
@ -36,14 +36,16 @@ report
-- ^ The number of columns for the report -- ^ The number of columns for the report
-> ProgState -> ProgState
-- ^ The program state -- ^ The program state
-> String -> [String]
report width s report width s
= standingsReport width s = standingsReport width s
++ "\n" ++ [""]
++ gameStatsReport width s ++ gameStatsReport width s
++ [""]
++ yearToDateStatsReport width s
standingsReport :: Int -> ProgState -> String standingsReport :: Int -> ProgState -> [String]
standingsReport width s = unlines $ fromMaybe [] $ do standingsReport width s = fromMaybe [] $ do
let let
db = s^.database db = s^.database
gs = s^.progMode.gameStateL gs = s^.progMode.gameStateL
@ -88,20 +90,32 @@ standingsReport width s = unlines $ fromMaybe [] $ do
++ showStats tStats ++ showStats tStats
] ]
gameStatsReport :: Int -> ProgState -> String gameStatsReport :: Int -> ProgState -> [String]
gameStatsReport width s = unlines $ fromMaybe [] $ do gameStatsReport width s = playerReport width "GAME" $
pStats <- mapM fromMaybe [] $ mapM
(\(pid, stats) -> do (\(pid, stats) -> do
p <- nth pid $ s^.database.dbPlayers p <- nth pid $ s^.database.dbPlayers
Just (p, stats)) Just (p, stats))
(M.toList $ s^.progMode.gameStateL.gamePlayerStats) (M.toList $ s^.progMode.gameStateL.gamePlayerStats)
let
nameWidth = succ $ maximum $ 10 : map yearToDateStatsReport :: Int -> ProgState -> [String]
(length . (^.pName) . fst) yearToDateStatsReport width s = playerReport width "YEAR TO DATE" $
pStats map (\p -> (p, p^.pYtd)) $
tStats = foldr (addPlayerStats . snd) newPlayerStats pStats filter playerIsActive $ s^.database.dbPlayers
Just $
[ centre width "GAME STATISTICS" gameDate :: GameState -> String
gameDate gs = fromMaybe "" $ do
year <- show <$> gs^.gameYear
month <- month <$> gs^.gameMonth
day <- padNum 2 <$> gs^.gameDay
Just $ month ++ " " ++ day ++ " " ++ year
playerReport :: Int -> String -> [(Player, PlayerStats)] -> [String]
playerReport width label ps = let
nameWidth = playerNameColWidth $ map fst ps
tStats = foldr (addPlayerStats . snd) newPlayerStats ps
in
[ centre width (label ++ " STATISTICS")
, "" , ""
, centre width , centre width
$ "NO. " $ "NO. "
@ -119,12 +133,12 @@ gameStatsReport width s = unlines $ fromMaybe [] $ do
++ right 6 (show $ stats^.psAssists) ++ right 6 (show $ stats^.psAssists)
++ right 6 (show $ psPoints stats) ++ right 6 (show $ psPoints stats)
++ right 6 (show $ stats^.psPMin)) ++ right 6 (show $ stats^.psPMin))
pStats ++ ps ++
[ centre width [ centre width
$ replicate (4 + nameWidth) ' ' $ replicate (4 + nameWidth) ' '
++ replicate (3 + 3 * 6) '-' ++ replicate (3 + 3 * 6) '-'
, overlay , overlay
"GAME TOTALS" (label ++ " TOTALS")
( centre width ( centre width
$ replicate (4 + nameWidth) ' ' $ replicate (4 + nameWidth) ' '
++ right 3 (show $ tStats^.psGoals) ++ right 3 (show $ tStats^.psGoals)
@ -134,12 +148,10 @@ gameStatsReport width s = unlines $ fromMaybe [] $ do
) )
] ]
gameDate :: GameState -> String playerNameColWidth :: [Player] -> Int
gameDate gs = fromMaybe "" $ do playerNameColWidth = foldr
year <- show <$> gs^.gameYear (\player current -> max current $ succ $ length $ player^.pName)
month <- month <$> gs^.gameMonth 10
day <- padNum 2 <$> gs^.gameDay
Just $ month ++ " " ++ day ++ " " ++ year
showStats :: GameStats -> String showStats :: GameStats -> String
showStats gs showStats gs

View File

@ -42,6 +42,7 @@ module Mtlstats.Types (
database, database,
progMode, progMode,
inputBuffer, inputBuffer,
scrollOffset,
-- ** ProgMode Lenses -- ** ProgMode Lenses
gameStateL, gameStateL,
createPlayerStateL, createPlayerStateL,
@ -132,6 +133,7 @@ module Mtlstats.Types (
playerSearchExact, playerSearchExact,
modifyPlayer, modifyPlayer,
playerSummary, playerSummary,
playerIsActive,
-- ** PlayerStats Helpers -- ** PlayerStats Helpers
psPoints, psPoints,
addPlayerStats addPlayerStats
@ -172,12 +174,14 @@ type Action a = StateT ProgState C.Curses a
-- | Represents the program state -- | Represents the program state
data ProgState = ProgState data ProgState = ProgState
{ _database :: Database { _database :: Database
-- ^ The data to be saved -- ^ The data to be saved
, _progMode :: ProgMode , _progMode :: ProgMode
-- ^ The program's mode -- ^ The program's mode
, _inputBuffer :: String , _inputBuffer :: String
-- ^ Buffer for user input -- ^ Buffer for user input
, _scrollOffset :: Int
-- ^ The scrolling offset for the display
} }
-- | The program mode -- | The program mode
@ -507,9 +511,10 @@ createPlayerStateL = lens
-- | Constructor for a 'ProgState' -- | Constructor for a 'ProgState'
newProgState :: ProgState newProgState :: ProgState
newProgState = ProgState newProgState = ProgState
{ _database = newDatabase { _database = newDatabase
, _progMode = MainMenu , _progMode = MainMenu
, _inputBuffer = "" , _inputBuffer = ""
, _scrollOffset = 0
} }
-- | Constructor for a 'GameState' -- | Constructor for a 'GameState'
@ -732,6 +737,16 @@ playerSummary :: Player -> String
playerSummary p = playerSummary p =
p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition p^.pName ++ " (" ++ show (p^.pNumber) ++ ") " ++ p^.pPosition
-- | Determines whether or not a player has been active in the current
-- season/year
playerIsActive :: Player -> Bool
playerIsActive = do
stats <- (^.pYtd)
return
$ stats^.psGoals /= 0
|| stats^.psAssists /= 0
|| stats^.psPMin /= 0
-- | Calculates a player's points -- | Calculates a player's points
psPoints :: PlayerStats -> Int psPoints :: PlayerStats -> Int
psPoints s = s^.psGoals + s^.psAssists psPoints s = s^.psGoals + s^.psAssists

View File

@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
module Mtlstats.Util (nth, modifyNth, updateMap) where module Mtlstats.Util (nth, modifyNth, updateMap, slice) where
import qualified Data.Map as M import qualified Data.Map as M
@ -64,3 +64,14 @@ updateMap
updateMap k def f m = let updateMap k def f m = let
x = M.findWithDefault def k m x = M.findWithDefault def k m
in M.insert k (f x) m in M.insert k (f x) m
-- | Selects a section of a list
slice
:: Int
-- ^ The index to start at
-> Int
-- ^ The number of elements to take
-> [a]
-- ^ The list to take a subset of
-> [a]
slice offset len = take len . drop offset

View File

@ -19,6 +19,8 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE LambdaCase #-}
module ActionsSpec (spec) where module ActionsSpec (spec) where
import Control.Monad (replicateM) import Control.Monad (replicateM)
@ -26,7 +28,16 @@ import qualified Data.Map as M
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
import Lens.Micro ((^.), (&), (.~), (?~), (%~)) import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import System.Random (randomRIO) import System.Random (randomRIO)
import Test.Hspec (Spec, context, describe, it, runIO, shouldBe, shouldNotBe) import Test.Hspec
( Spec
, context
, describe
, it
, runIO
, shouldBe
, shouldNotBe
, shouldSatisfy
)
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Types import Mtlstats.Types
@ -49,6 +60,9 @@ spec = describe "Mtlstats.Actions" $ do
awardAssistSpec awardAssistSpec
resetGoalDataSpec resetGoalDataSpec
assignPMinsSpec assignPMinsSpec
backHomeSpec
scrollUpSpec
scrollDownSpec
startNewSeasonSpec :: Spec startNewSeasonSpec :: Spec
startNewSeasonSpec = describe "startNewSeason" $ do startNewSeasonSpec = describe "startNewSeason" $ do
@ -640,3 +654,49 @@ makeNum = randomRIO (1, 10)
makeName :: IO String makeName :: IO String
makeName = replicateM 10 $ randomRIO ('A', 'Z') makeName = replicateM 10 $ randomRIO ('A', 'Z')
backHomeSpec :: Spec
backHomeSpec = describe "backHome" $ do
let
input = newProgState
& progMode.gameStateL .~ newGameState
& inputBuffer .~ "foo"
& scrollOffset .~ 123
result = backHome input
it "should set the program mode back to MainMenu" $
result^.progMode `shouldSatisfy` \case
MainMenu -> True
_ -> False
it "should clear the input buffer" $
result^.inputBuffer `shouldBe` ""
it "should reset the scroll offset" $
result^.scrollOffset `shouldBe` 0
scrollUpSpec :: Spec
scrollUpSpec = describe "scrollUp" $ do
context "scrolled down" $
it "should decrease the scroll offset by one" $ let
ps = newProgState & scrollOffset .~ 10
ps' = scrollUp ps
in ps'^.scrollOffset `shouldBe` 9
context "at top" $
it "should keep the scroll offset at zero" $ let
ps = scrollUp newProgState
in ps^.scrollOffset `shouldBe` 0
context "above top" $
it "should return the scroll offset to zero" $ let
ps = newProgState & scrollOffset .~ (-10)
ps' = scrollUp ps
in ps'^.scrollOffset `shouldBe` 0
scrollDownSpec = describe "scrollDown" $
it "should increase the scroll offset" $ let
ps = newProgState & scrollOffset .~ 10
ps' = scrollDown ps
in ps'^.scrollOffset `shouldBe` 11

View File

@ -28,8 +28,9 @@ import Mtlstats.Report
import Mtlstats.Types import Mtlstats.Types
spec :: Spec spec :: Spec
spec = describe "Mtlstats.Report" spec = describe "Mtlstats.Report" $ do
gameDateSpec gameDateSpec
playerNameColWidthSpec
gameDateSpec :: Spec gameDateSpec :: Spec
gameDateSpec = describe "gameDate" $ do gameDateSpec = describe "gameDate" $ do
@ -45,3 +46,20 @@ gameDateSpec = describe "gameDate" $ do
context "invalid date" $ context "invalid date" $
it "should return an empty string" $ it "should return an empty string" $
gameDate newGameState `shouldBe` "" gameDate newGameState `shouldBe` ""
playerNameColWidthSpec :: Spec
playerNameColWidthSpec = describe "playerNameColWidth" $ do
let
short1 = newPlayer 1 "short" "foo"
short2 = newPlayer 2 "shorty" "bar"
long = newPlayer 3 "123456789012345" "baz"
mapM_
(\(label, players, expected) -> context label $
it ("should be " ++ show expected) $
playerNameColWidth players `shouldBe` expected)
-- label, players, expected
[ ( "empty list", [], 10 )
, ( "short names", [short1, short2], 10 )
, ( "long name", [short1, long], 16 )
]

View File

@ -58,6 +58,7 @@ spec = describe "Mtlstats.Types" $ do
playerSearchExactSpec playerSearchExactSpec
modifyPlayerSpec modifyPlayerSpec
playerSummarySpec playerSummarySpec
playerIsActiveSpec
psPointsSpec psPointsSpec
addPlayerStatsSpec addPlayerStatsSpec
Menu.spec Menu.spec
@ -567,6 +568,26 @@ playerSummarySpec = describe "playerSummary" $
it "should be \"Joe (2) center\"" $ it "should be \"Joe (2) center\"" $
playerSummary joe `shouldBe` "Joe (2) center" playerSummary joe `shouldBe` "Joe (2) center"
playerIsActiveSpec :: Spec
playerIsActiveSpec = describe "playerIsActive" $ do
let
pState = newPlayerStats
& psGoals .~ 10
& psAssists .~ 11
& psPMin .~ 12
player = newPlayer 1 "Joe" "centre" & pLifetime .~ pState
mapM_
(\(label, player', expected) -> context label $
it ("should be " ++ show expected) $
playerIsActive player' `shouldBe` expected)
-- label, player, expected
[ ( "not active", player, False )
, ( "has goal", player & pYtd.psGoals .~ 1, True )
, ( "has assist", player & pYtd.psAssists .~ 1, True )
, ( "has penalty minute", player & pYtd.psPMin .~ 1, True )
]
psPointsSpec :: Spec psPointsSpec :: Spec
psPointsSpec = describe "psPoints" $ mapM_ psPointsSpec = describe "psPoints" $ mapM_
(\(goals, assists, points) -> let (\(goals, assists, points) -> let

View File

@ -31,6 +31,7 @@ spec = describe "Mtlstats.Util" $ do
nthSpec nthSpec
modifyNthSpec modifyNthSpec
updateMapSpec updateMapSpec
sliceSpec
nthSpec :: Spec nthSpec :: Spec
nthSpec = describe "nth" $ mapM_ nthSpec = describe "nth" $ mapM_
@ -75,3 +76,19 @@ updateMapSpec = describe "updateMap" $ do
expected = M.fromList [(1, 2), (3, 5), (10, 11)] expected = M.fromList [(1, 2), (3, 5), (10, 11)]
in it "should create a new value and update the default" $ in it "should create a new value and update the default" $
updateMap 10 10 succ input `shouldBe` expected updateMap 10 10 succ input `shouldBe` expected
sliceSpec :: Spec
sliceSpec = describe "slice" $ do
let list = [2, 4, 6, 8]
context "sublist" $
it "should return the sublist" $
slice 1 2 list `shouldBe` [4, 6]
context "too large" $
it "should return as much of the list as possible" $
slice 1 100 list `shouldBe` [4, 6, 8]
context "negative offset" $
it "should return the correct number of elements from the beginning" $
slice (-10) 2 list `shouldBe` [2, 4]