10 Commits

Author SHA1 Message Date
Jonathan Lamothe
f9085832f4 version 0.14.0 2020-03-05 16:56:48 -05:00
Jonathan Lamothe
e15623bde3 Merge pull request #79 from mtlstats/report-file
output report to a text file (report.txt)
2020-03-05 16:54:55 -05:00
Jonathan Lamothe
db62fbb542 output report to a text file (report.txt) 2020-03-05 16:45:40 -05:00
Jonathan Lamothe
4a8515b862 Merge pull request #78 from mtlstats/fix-shutouts
Fix shutouts
2020-03-05 05:35:17 -05:00
Jonathan Lamothe
e4c668d1e4 updated change log 2020-03-05 05:28:56 -05:00
Jonathan Lamothe
9ee33cbd03 hlint suggestions 2020-03-05 05:26:25 -05:00
Jonathan Lamothe
53c49492cb fixed shutout bug
shutouts weren't being recorded
2020-03-05 05:26:25 -05:00
Jonathan Lamothe
4d1eaa1523 Merge branch 'master' into dev 2020-03-05 05:24:57 -05:00
Jonathan Lamothe
8a8a550854 Merge pull request #77 from mtlstats/vagrant
vagrant setup
2020-03-03 14:33:58 -05:00
Jonathan Lamothe
6227df8e01 vagrant setup 2020-03-03 14:23:13 -05:00
17 changed files with 297 additions and 132 deletions

3
.gitignore vendored
View File

@@ -1,3 +1,6 @@
.stack-work/ .stack-work/
mtlstats.cabal mtlstats.cabal
.vagrant
data
*.log
*~ *~

View File

@@ -1,5 +1,9 @@
# Changelog for mtlstats # Changelog for mtlstats
## 0.14.0
- Fixed a bug that was causing shutouts to not be recorded
- Output report to a text file (report.txt)
## 0.13.0 ## 0.13.0
- Added autocomplete to player position prompt - Added autocomplete to player position prompt
- Don't prompt for lifetime stats on rookie player/goalie creation - Don't prompt for lifetime stats on rookie player/goalie creation

10
Vagrantfile vendored Normal file
View File

@@ -0,0 +1,10 @@
# -*- mode: ruby -*-
# vi: set ft=ruby :
Vagrant.configure("2") do |config|
config.vm.box = "ubuntu/xenial64"
config.vm.provision "shell", path: "vagrant/provision.sh"
config.vm.provider :virtualbox do |v|
v.customize ["modifyvm", :id, "--memory", 4096]
end
end

View File

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

View File

@@ -124,12 +124,13 @@ awardGoal n ps = ps
(\m -> let (\m -> let
stats = M.findWithDefault newPlayerStats n m stats = M.findWithDefault newPlayerStats n m
in M.insert n (stats & psGoals %~ succ) m) in M.insert n (stats & psGoals %~ succ) m)
& database.dbPlayers %~ map & database.dbPlayers %~ zipWith
(\(i, p) -> if i == n (\i p -> if i == n
then p then p
& pYtd.psGoals %~ succ & pYtd.psGoals %~ succ
& pLifetime.psGoals %~ succ & pLifetime.psGoals %~ succ
else p) . zip [0..] else p)
[0..]
-- | Awards an assist to a player -- | Awards an assist to a player
awardAssist awardAssist
@@ -142,12 +143,13 @@ awardAssist n ps = ps
(\m -> let (\m -> let
stats = M.findWithDefault newPlayerStats n m stats = M.findWithDefault newPlayerStats n m
in M.insert n (stats & psAssists %~ succ) m) in M.insert n (stats & psAssists %~ succ) m)
& database.dbPlayers %~ map & database.dbPlayers %~ zipWith
(\(i, p) -> if i == n (\i p -> if i == n
then p then p
& pYtd.psAssists %~ succ & pYtd.psAssists %~ succ
& pLifetime.psAssists %~ succ & pLifetime.psAssists %~ succ
else p) . zip [0..] else p)
[0..]
-- | Resets the entered data for the current goal -- | Resets the entered data for the current goal
resetGoalData :: ProgState -> ProgState resetGoalData :: ProgState -> ProgState

View File

@@ -87,18 +87,22 @@ setGameGoalie
-> ProgState -> ProgState
setGameGoalie gid s = fromMaybe s $ do setGameGoalie gid s = fromMaybe s $ do
let gs = s^.progMode.gameStateL let gs = s^.progMode.gameStateL
won <- gameWon gs won <- gameWon gs
lost <- gameLost gs lost <- gameLost gs
tied <- gs^.overtimeFlag tied <- gs^.overtimeFlag
shutout <- (==0) <$> otherScore gs
let let
w = if won then 1 else 0 w = if won then 1 else 0
l = if lost then 1 else 0 l = if lost then 1 else 0
t = if tied then 1 else 0 t = if tied then 1 else 0
so = if shutout then 1 else 0
updateStats updateStats
= (gsWins +~ w) = (gsWins +~ w)
. (gsLosses +~ l) . (gsLosses +~ l)
. (gsTies +~ t) . (gsTies +~ t)
. (gsShutouts +~ so)
updateGoalie updateGoalie
= (gYtd %~ updateStats) = (gYtd %~ updateStats)

View File

@@ -44,3 +44,11 @@ maxAssists = 2
-- | The length of a typical game (in minutes) -- | The length of a typical game (in minutes)
gameLength :: Int gameLength :: Int
gameLength = 60 gameLength = 60
-- | Report output filename
reportFilename :: FilePath
reportFilename = "report.txt"
-- | Number of columns in report file
reportCols :: Int
reportCols = 79

View File

@@ -21,13 +21,15 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Control.NewGame (newGameC) where module Mtlstats.Control.NewGame (newGameC) where
import Control.Monad.Trans.State (gets, modify) import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State (get, gets, modify)
import Data.Maybe (fromJust, fromMaybe, isJust) import Data.Maybe (fromJust, fromMaybe, isJust)
import Lens.Micro ((^.), (.~)) import Lens.Micro ((^.), (.~))
import qualified UI.NCurses as C import qualified UI.NCurses as C
import Mtlstats.Actions import Mtlstats.Actions
import Mtlstats.Actions.NewGame import Mtlstats.Actions.NewGame
import Mtlstats.Config
import Mtlstats.Control.NewGame.GoalieInput import Mtlstats.Control.NewGame.GoalieInput
import Mtlstats.Format import Mtlstats.Format
import Mtlstats.Handlers import Mtlstats.Handlers
@@ -211,9 +213,12 @@ reportC = Controller
C.EventSpecialKey C.KeyUpArrow -> modify scrollUp C.EventSpecialKey C.KeyUpArrow -> modify scrollUp
C.EventSpecialKey C.KeyDownArrow -> modify scrollDown C.EventSpecialKey C.KeyDownArrow -> modify scrollDown
C.EventSpecialKey C.KeyHome -> modify $ scrollOffset .~ 0 C.EventSpecialKey C.KeyHome -> modify $ scrollOffset .~ 0
C.EventSpecialKey _ -> modify backHome
C.EventCharacter _ -> modify backHome C.EventCharacter '\n' -> do
_ -> return () get >>= liftIO . writeFile reportFilename . unlines . report reportCols
modify backHome
_ -> return ()
return True return True
} }

View File

@@ -170,10 +170,11 @@ gameGoalieMenu s = let
goalie <- nth n $ s^.database.dbGoalies goalie <- nth n $ s^.database.dbGoalies
Just (n, goalie)) Just (n, goalie))
gids gids
in Menu title () $ map in Menu title () $ zipWith
(\(ch, (gid, goalie)) -> MenuItem ch (goalieSummary goalie) $ (\ch (gid, goalie) -> MenuItem ch (goalieSummary goalie) $
modify $ GI.setGameGoalie gid) $ modify $ GI.setGameGoalie gid)
zip ['1'..] goalies ['1'..]
goalies
-- | The edit menu -- | The edit menu
editMenu :: Menu () editMenu :: Menu ()

View File

@@ -164,9 +164,7 @@ numPromptWithFallback pStr fallback act = Prompt
, promptProcessChar = \ch str -> if isDigit ch , promptProcessChar = \ch str -> if isDigit ch
then str ++ [ch] then str ++ [ch]
else str else str
, promptAction = \inStr -> case readMaybe inStr of , promptAction = maybe fallback act . readMaybe
Nothing -> fallback
Just n -> act n
, promptSpecialKey = const $ return () , promptSpecialKey = const $ return ()
} }

View File

@@ -241,8 +241,7 @@ filteredPlayerReport width label criteria showTotals lineNumbers ps = let
else repeat "" else repeat ""
table = overlayLast olayText table = overlayLast olayText
$ map (\(ln, line) -> overlay ln $ centre width line) $ zipWith (\ln line -> overlay ln $ centre width line) lnOverlay
$ zip lnOverlay
$ complexTable ([right, left] ++ repeat right) $ complexTable ([right, left] ++ repeat right)
$ tHeader : body ++ if showTotals $ tHeader : body ++ if showTotals
then [separator, totals] then [separator, totals]
@@ -301,8 +300,7 @@ goalieReport width showTotals lineNumbers goalieData = let
then "" : [right 2 $ show x | x <- [(1 :: Int)..]] then "" : [right 2 $ show x | x <- [(1 :: Int)..]]
else repeat "" else repeat ""
in map (\(ln, line) -> overlay ln $ centre width line) in zipWith (\ln line -> overlay ln $ centre width line) lnOverlay
$ zip lnOverlay
$ overlayLast olayText $ overlayLast olayText
$ complexTable ([right, left] ++ repeat right) $ complexTable ([right, left] ++ repeat right)
$ header : body ++ if showTotals $ header : body ++ if showTotals

View File

@@ -208,9 +208,8 @@ import Data.Aeson
, (.=) , (.=)
) )
import Data.Char (toUpper) import Data.Char (toUpper)
import Data.List (isInfixOf) import Data.List (find, isInfixOf)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (listToMaybe)
import Lens.Micro (Lens', lens, (&), (^.), (.~)) import Lens.Micro (Lens', lens, (&), (^.), (.~))
import Lens.Micro.TH (makeLenses) import Lens.Micro.TH (makeLenses)
import qualified UI.NCurses as C import qualified UI.NCurses as C
@@ -1019,7 +1018,7 @@ playerSearchExact
-> Maybe (Int, Player) -> Maybe (Int, Player)
-- ^ The player's index and value -- ^ The player's index and value
playerSearchExact sStr = playerSearchExact sStr =
listToMaybe . filter match . zip [0..] find match . zip [0..]
where match (_, p) = p^.pName == sStr where match (_, p) = p^.pName == sStr
-- | Modifies a player with a given name -- | Modifies a player with a given name

View File

@@ -52,8 +52,9 @@ modifyNth
-> [a] -> [a]
-- ^ The list -- ^ The list
-> [a] -> [a]
modifyNth n f = map (\(i, x) -> if i == n then f x else x) modifyNth n f = zipWith
. zip [0..] (\i x -> if i == n then f x else x)
[0..]
-- | Modify a value indexed by a given key in a map using a default -- | Modify a value indexed by a given key in a map using a default
-- initial value if not present -- initial value if not present

View File

@@ -33,7 +33,7 @@ import Mtlstats.Util
import qualified TypesSpec as TS import qualified TypesSpec as TS
spec :: Spec spec :: Spec
spec = describe "Mtlstats.Actions.GoalieInput" $ do spec = describe "GoalieInput" $ do
finishGoalieEntrySpec finishGoalieEntrySpec
recordGoalieStatsSpec recordGoalieStatsSpec
setGameGoalieSpec setGameGoalieSpec
@@ -208,107 +208,175 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
] ]
setGameGoalieSpec :: Spec setGameGoalieSpec :: Spec
setGameGoalieSpec = describe "setGameGoalie" $ let setGameGoalieSpec = describe "setGameGoalie" $ mapM_
goalieStats w l t = newGoalieStats (\(label, goalieId, ps, expectedJoe, expectedBob, expectedGStats) ->
& gsWins .~ w context label $ do
& gsLosses .~ l
& gsTies .~ t
bob = newGoalie 2 "Bob" let
& gYtd .~ goalieStats 10 11 12 ps' = setGameGoalie goalieId ps
& gLifetime .~ goalieStats 20 21 22 [joe', bob'] = ps'^.database.dbGoalies
gStats' = ps'^.progMode.gameStateL.gameGoalieStats
joe = newGoalie 3 "Joe" context "Joe" $ joe' `TS.compareTest` expectedJoe
& gYtd .~ goalieStats 30 31 32 context "Bob" $ bob' `TS.compareTest` expectedBob
& gLifetime .~ goalieStats 40 41 42 context "game stats" $ gStats' `TS.compareTest` expectedGStats)
gameState h a ot = newGameState [ ( "Joe wins - no shutout"
& gameType ?~ HomeGame , 0
& homeScore ?~ h , psWin
& awayScore ?~ a , joeWin
& overtimeFlag ?~ ot , bob
, gsJoeWin
)
winningGame = gameState 1 0 False , ( "Bob wins - no shutout"
losingGame = gameState 0 1 False , 1
tiedGame = gameState 0 1 True , psWin
, joe
, bobWin
, gsBobWin
)
in mapM_ , ( "Joe wins - shutout"
(\(setLabel, gs, setGid, bobData, joeData) -> context setLabel $ let , 0
, psWinSO
, joeWinSO
, bob
, gsJoeWinSO
)
progState = newProgState , ( "Bob wins - shutout"
& database.dbGoalies .~ [bob, joe] , 1
& progMode.gameStateL .~ gs , psWinSO
& setGameGoalie setGid , joe
, bobWinSO
, gsBobWinSO
)
in mapM_ , ( "Joe loses"
(\( chkLabel , 0
, chkGid , psLose
, ( gWins , joeLose
, gLosses , bob
, gTies , gsJoeLose
, ytdWins )
, ytdLosses
, ytdTies
, ltWins
, ltLosses
, ltTies
)
) -> context chkLabel $ do
let
goalie = (progState^.database.dbGoalies) !! chkGid
gameStats = progState^.progMode.gameStateL.gameGoalieStats
game = M.findWithDefault newGoalieStats chkGid gameStats
ytd = goalie^.gYtd
lifetime = goalie^.gLifetime
mapM_ , ( "Bob loses"
(\(label', expected, actual) -> context label' $ , 1
expected `TS.compareTest` actual) , psLose
[ ( "game stats", game, goalieStats gWins gLosses gTies ) , joe
, ( "YTD stats", ytd, goalieStats ytdWins ytdLosses ytdTies ) , bobLose
, ( "lifetime stats", lifetime, goalieStats ltWins ltLosses ltTies ) , gsBobLose
] )
it "should set the gameGoalieAssigned flag" $ , ( "Joe overtime"
progState^.progMode.gameStateL.gameGoalieAssigned `shouldBe` True) , 0
[ ( "checking Bob", 0, bobData ) , psOT
, ( "checking Joe", 1, joeData ) , joeOT
]) , bob
[ ( "Bob wins" , gsJoeOT
, winningGame )
, 0
, ( 1, 0, 0, 11, 11, 12, 21, 21, 22 ) , ( "Bob overtime"
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 ) , 1
) , psOT
, ( "Bob loses" , joe
, losingGame , bobOT
, 0 , gsBobOT
, ( 0, 1, 0, 10, 12, 12, 20, 22, 22 ) )
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 ) ]
)
, ( "Bob ties" where
, tiedGame
, 0 joe
, ( 0, 0, 1, 10, 11, 13, 20, 21, 23 ) = newGoalie 2 "Joe"
, ( 0, 0, 0, 30, 31, 32, 40, 41, 42 ) & gYtd
) %~ (gsShutouts .~ 11)
, ( "Joe wins" . (gsWins .~ 12)
, winningGame . (gsLosses .~ 13)
, 1 . (gsTies .~ 14)
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 ) & gLifetime
, ( 1, 0, 0, 31, 31, 32, 41, 41, 42 ) %~ (gsShutouts .~ 21)
) . (gsWins .~ 22)
, ( "Joe loses" . (gsLosses .~ 23)
, losingGame . (gsTies .~ 24)
, 1
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 ) bob
, ( 0, 1, 0, 30, 32, 32, 40, 42, 42 ) = newGoalie 3 "Bob"
) & gYtd
, ( "Joe ties" %~ (gsShutouts .~ 31)
, tiedGame . (gsWins .~ 32)
, 1 . (gsLosses .~ 33)
, ( 0, 0, 0, 10, 11, 12, 20, 21, 22 ) . (gsTies .~ 34)
, ( 0, 0, 1, 30, 31, 33, 40, 41, 43 ) & gLifetime
) %~ (gsShutouts .~ 41)
] . (gsWins .~ 42)
. (gsLosses .~ 43)
. (gsTies .~ 44)
joeWin = win joe
bobWin = win bob
joeWinSO = winSO joe
bobWinSO = winSO bob
joeLose = lose joe
bobLose = lose bob
joeOT = tie joe
bobOT = tie bob
psWin = mkProgState
$ (homeScore ?~ 2)
. (awayScore ?~ 1)
psWinSO = mkProgState
$ (homeScore ?~ 1)
. (awayScore ?~ 0)
psLose = mkProgState
$ (homeScore ?~ 0)
. (awayScore ?~ 1)
psOT = mkProgState
$ (homeScore ?~ 0)
. (awayScore ?~ 1)
. (overtimeFlag ?~ True)
mkProgState f
= newProgState
& database.dbGoalies .~ [joe, bob]
& progMode.gameStateL
%~ f
. (gameType ?~ HomeGame)
. (overtimeFlag ?~ False)
gsJoeWin = mkGameStats 0 incWin
gsBobWin = mkGameStats 1 incWin
gsJoeWinSO = mkGameStats 0 $ incWin . incSO
gsBobWinSO = mkGameStats 1 $ incWin . incSO
gsJoeLose = mkGameStats 0 incLoss
gsBobLose = mkGameStats 1 incLoss
gsJoeOT = mkGameStats 0 incOT
gsBobOT = mkGameStats 1 incOT
mkGameStats n f = M.fromList [(n, f newGoalieStats)]
win
= (gYtd %~ incWin)
. (gLifetime %~ incWin)
winSO
= (gYtd %~ (incWin . incSO))
. (gLifetime %~ (incWin . incSO))
lose
= (gYtd %~ incLoss)
. (gLifetime %~ incLoss)
tie
= (gYtd %~ incOT)
. (gLifetime %~ incOT)
incWin = gsWins %~ succ
incSO = gsShutouts %~ succ
incLoss = gsLosses %~ succ
incOT = gsTies %~ succ

View File

@@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE OverloadedStrings, RankNTypes #-} {-# LANGUAGE FlexibleInstances, OverloadedStrings, RankNTypes #-}
module TypesSpec module TypesSpec
( Comparable (..) ( Comparable (..)
@@ -33,6 +33,7 @@ module TypesSpec
import Control.Monad (replicateM) import Control.Monad (replicateM)
import Data.Aeson (FromJSON, ToJSON, decode, encode, toJSON) import Data.Aeson (FromJSON, ToJSON, decode, encode, toJSON)
import Data.Aeson.Types (Value (Object)) import Data.Aeson.Types (Value (Object))
import qualified Data.Map.Lazy as M
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.Ratio ((%)) import Data.Ratio ((%))
import Lens.Micro (Lens', (&), (^.), (.~), (?~)) import Lens.Micro (Lens', (&), (^.), (.~), (?~))
@@ -1005,3 +1006,48 @@ instance Comparable EditStandingsMode where
compareTest actual expected = compareTest actual expected =
it ("should be " ++ show expected) $ it ("should be " ++ show expected) $
actual `shouldBe` expected actual `shouldBe` expected
instance Comparable Goalie where
compareTest actual expected = do
describe "gNumber" $
it ("should be " ++ show (expected^.gNumber)) $
actual^.gNumber `shouldBe` expected^.gNumber
describe "gName" $
it ("should be " ++ show (expected^.gName)) $
actual^.gName `shouldBe` expected^.gName
describe "gRookie" $
it ("should be " ++ show (expected^.gRookie)) $
actual^.gRookie `shouldBe` expected^.gRookie
describe "gActive" $
it ("should be " ++ show (expected^.gActive)) $
actual^.gActive `shouldBe` expected^.gActive
describe "gYtd" $
(actual^.gYtd) `compareTest` (expected^.gYtd)
describe "gLifetime" $
(actual^.gLifetime) `compareTest` (expected^.gLifetime)
instance Comparable (M.Map Int GoalieStats) where
compareTest actual expected = do
let
aList = M.toList actual
eList = M.toList expected
it "should have the correct number of elements" $
length aList `shouldBe` length eList
mapM_
(\(n, (ka, va), (ke, ve)) -> context ("element " ++ show n) $ do
context "key" $
it ("should be " ++ show ke) $
ka `shouldBe` ke
context "value" $ va `compareTest` ve)
(zip3 ([0..] :: [Int]) aList eList)

8
vagrant/as_user.sh Executable file
View File

@@ -0,0 +1,8 @@
#!/bin/sh
echo "export PATH=\"$HOME/.local/bin:$PATH\"" >>~vagrant/.bashrc
mkdir /vagrant/data
ln -s /vagrant/data ~vagrant/.mtlstats
cd /vagrant
stack install

10
vagrant/provision.sh Executable file
View File

@@ -0,0 +1,10 @@
#!/bin/sh
apt-get update
apt-get upgrade
apt-get -y install libghc-ncurses-dev
wget -qO- https://get.haskellstack.org/ | sh
export HOME=/home/vagrant
sudo -u vagrant /vagrant/vagrant/as_user.sh