Compare commits
27 Commits
| Author | SHA1 | Date | |
|---|---|---|---|
|
|
99baebe144 | ||
|
|
eb3714c40a | ||
|
|
1bd3ae9564 | ||
|
|
2adfe9b016 | ||
|
|
85a8e3baf1 | ||
|
|
393a2c6dc4 | ||
|
|
ed240c6a38 | ||
|
|
4f147cd5a4 | ||
|
|
9b6dfc4be9 | ||
|
|
c20fb30f5b | ||
|
|
3c0e690ed3 | ||
|
|
f37e231623 | ||
|
|
fbaf2a1e60 | ||
|
|
65979329bd | ||
|
|
ded019faac | ||
|
|
1322004d38 | ||
|
|
2cb279e7e7 | ||
|
|
7ca66ad801 | ||
|
|
82544046ce | ||
|
|
95c97d722e | ||
|
|
0eb46cacce | ||
|
|
25f887a5e8 | ||
|
|
7ba670948b | ||
|
|
ca06b0570e | ||
|
|
1e8473538a | ||
|
|
87336dcd1d | ||
|
|
ffa241c1f7 |
11
ChangeLog.md
11
ChangeLog.md
@@ -1,5 +1,16 @@
|
|||||||
# Changelog for mtlstats
|
# Changelog for mtlstats
|
||||||
|
|
||||||
|
## 0.15.2
|
||||||
|
- allow ties
|
||||||
|
|
||||||
|
## 0.15.1
|
||||||
|
- only search for active players/goalies on game data input
|
||||||
|
|
||||||
|
## 0.15.0
|
||||||
|
- Ask for database to load on start-up
|
||||||
|
- Add page break to report file
|
||||||
|
- Implemented player/goalie deletion
|
||||||
|
|
||||||
## 0.14.0
|
## 0.14.0
|
||||||
- Fixed a bug that was causing shutouts to not be recorded
|
- Fixed a bug that was causing shutouts to not be recorded
|
||||||
- Output report to a text file (report.txt)
|
- Output report to a text file (report.txt)
|
||||||
|
|||||||
@@ -1,5 +1,5 @@
|
|||||||
name: mtlstats
|
name: mtlstats
|
||||||
version: 0.14.0
|
version: 0.15.2
|
||||||
github: "mtlstats/mtlstats"
|
github: "mtlstats/mtlstats"
|
||||||
license: GPL-3
|
license: GPL-3
|
||||||
author: "Jonathan Lamothe"
|
author: "Jonathan Lamothe"
|
||||||
|
|||||||
@@ -19,23 +19,15 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
|
|
||||||
module Mtlstats (initState, mainLoop) where
|
module Mtlstats (initState, mainLoop) where
|
||||||
|
|
||||||
import Control.Exception (IOException, catch)
|
|
||||||
import Control.Monad (void)
|
import Control.Monad (void)
|
||||||
import Control.Monad.Extra (whenM)
|
import Control.Monad.Extra (whenM)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
|
||||||
import Control.Monad.Trans.Class (lift)
|
import Control.Monad.Trans.Class (lift)
|
||||||
import Control.Monad.Trans.State (get, gets)
|
import Control.Monad.Trans.State (get, gets)
|
||||||
import Data.Aeson (decodeFileStrict)
|
import Data.Maybe (fromJust)
|
||||||
import Data.Maybe (fromJust, fromMaybe)
|
|
||||||
import Lens.Micro ((&), (.~))
|
|
||||||
import System.EasyFile (getAppUserDataDirectory, (</>))
|
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
import Mtlstats.Config
|
|
||||||
import Mtlstats.Control
|
import Mtlstats.Control
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
|
|
||||||
@@ -44,15 +36,7 @@ initState :: C.Curses ProgState
|
|||||||
initState = do
|
initState = do
|
||||||
C.setEcho False
|
C.setEcho False
|
||||||
void $ C.setCursorMode C.CursorInvisible
|
void $ C.setCursorMode C.CursorInvisible
|
||||||
db <- liftIO $ do
|
return newProgState
|
||||||
dir <- getAppUserDataDirectory appName
|
|
||||||
let dbFile = dir </> dbFname
|
|
||||||
fromMaybe newDatabase <$> catch
|
|
||||||
(decodeFileStrict dbFile)
|
|
||||||
(\(_ :: IOException) -> return Nothing)
|
|
||||||
return
|
|
||||||
$ newProgState
|
|
||||||
& database .~ db
|
|
||||||
|
|
||||||
-- | Main program loop
|
-- | Main program loop
|
||||||
mainLoop :: Action ()
|
mainLoop :: Action ()
|
||||||
|
|||||||
@@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase, ScopedTypeVariables #-}
|
||||||
|
|
||||||
module Mtlstats.Actions
|
module Mtlstats.Actions
|
||||||
( startNewSeason
|
( startNewSeason
|
||||||
@@ -43,12 +43,14 @@ module Mtlstats.Actions
|
|||||||
, backHome
|
, backHome
|
||||||
, scrollUp
|
, scrollUp
|
||||||
, scrollDown
|
, scrollDown
|
||||||
|
, loadDatabase
|
||||||
, saveDatabase
|
, saveDatabase
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Control.Exception (IOException, catch)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Trans.State (gets, modify)
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Aeson (encodeFile)
|
import Data.Aeson (decodeFileStrict, encodeFile)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.), (&), (.~), (%~))
|
import Lens.Micro ((^.), (&), (.~), (%~))
|
||||||
import System.EasyFile
|
import System.EasyFile
|
||||||
@@ -216,12 +218,27 @@ scrollUp = scrollOffset %~ max 0 . pred
|
|||||||
scrollDown :: ProgState -> ProgState
|
scrollDown :: ProgState -> ProgState
|
||||||
scrollDown = scrollOffset %~ succ
|
scrollDown = scrollOffset %~ succ
|
||||||
|
|
||||||
|
-- | Loads the database
|
||||||
|
loadDatabase :: Action ()
|
||||||
|
loadDatabase = do
|
||||||
|
dbFile <- dbSetup
|
||||||
|
liftIO
|
||||||
|
(catch
|
||||||
|
(decodeFileStrict dbFile)
|
||||||
|
(\(_ :: IOException) -> return Nothing))
|
||||||
|
>>= mapM_ (modify . (database .~))
|
||||||
|
|
||||||
-- | Saves the database
|
-- | Saves the database
|
||||||
saveDatabase :: String -> Action ()
|
saveDatabase :: Action ()
|
||||||
saveDatabase fn = do
|
saveDatabase = do
|
||||||
db <- gets (^.database)
|
db <- gets (^.database)
|
||||||
|
dbFile <- dbSetup
|
||||||
|
liftIO $ encodeFile dbFile db
|
||||||
|
|
||||||
|
dbSetup :: Action String
|
||||||
|
dbSetup = do
|
||||||
|
fn <- gets (^.dbName)
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
dir <- getAppUserDataDirectory appName
|
dir <- getAppUserDataDirectory appName
|
||||||
let dbFile = dir </> fn
|
|
||||||
createDirectoryIfMissing True dir
|
createDirectoryIfMissing True dir
|
||||||
encodeFile dbFile db
|
return $ dir </> fn ++ ".json"
|
||||||
|
|||||||
@@ -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
|
||||||
|
|||||||
@@ -33,10 +33,6 @@ maxFunKeys = 9
|
|||||||
appName :: String
|
appName :: String
|
||||||
appName = "mtlstats"
|
appName = "mtlstats"
|
||||||
|
|
||||||
-- | The database filename
|
|
||||||
dbFname :: String
|
|
||||||
dbFname = "database.json"
|
|
||||||
|
|
||||||
-- | The maximum number of assists
|
-- | The maximum number of assists
|
||||||
maxAssists :: Int
|
maxAssists :: Int
|
||||||
maxAssists = 2
|
maxAssists = 2
|
||||||
|
|||||||
@@ -39,7 +39,7 @@ import Mtlstats.Types
|
|||||||
dispatch :: ProgState -> Controller
|
dispatch :: ProgState -> Controller
|
||||||
dispatch s = case s^.progMode of
|
dispatch s = case s^.progMode of
|
||||||
TitleScreen -> titleScreenC
|
TitleScreen -> titleScreenC
|
||||||
MainMenu -> mainMenuC
|
MainMenu -> mainMenuC s
|
||||||
NewSeason flag -> newSeasonC flag
|
NewSeason flag -> newSeasonC flag
|
||||||
NewGame gs -> newGameC gs
|
NewGame gs -> newGameC gs
|
||||||
EditMenu -> editMenuC
|
EditMenu -> editMenuC
|
||||||
@@ -49,11 +49,13 @@ dispatch s = case s^.progMode of
|
|||||||
EditGoalie egs -> editGoalieC egs
|
EditGoalie egs -> editGoalieC egs
|
||||||
(EditStandings esm) -> editStandingsC esm
|
(EditStandings esm) -> editStandingsC esm
|
||||||
|
|
||||||
mainMenuC :: Controller
|
mainMenuC :: ProgState -> Controller
|
||||||
mainMenuC = Controller
|
mainMenuC s = if null $ s^.dbName
|
||||||
{ drawController = const $ drawMenu mainMenu
|
then promptController getDBPrompt
|
||||||
, handleController = menuHandler mainMenu
|
else Controller
|
||||||
}
|
{ drawController = const $ drawMenu mainMenu
|
||||||
|
, handleController = menuHandler mainMenu
|
||||||
|
}
|
||||||
|
|
||||||
newSeasonC :: Bool -> Controller
|
newSeasonC :: Bool -> Controller
|
||||||
newSeasonC False = promptController newSeasonPrompt
|
newSeasonC False = promptController newSeasonPrompt
|
||||||
|
|||||||
@@ -23,10 +23,13 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
module Mtlstats.Control.EditGoalie (editGoalieC) where
|
module Mtlstats.Control.EditGoalie (editGoalieC) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.), (.~), (%~))
|
||||||
import UI.NCurses as C
|
import UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Actions
|
||||||
|
import Mtlstats.Handlers
|
||||||
import Mtlstats.Helpers.Goalie
|
import Mtlstats.Helpers.Goalie
|
||||||
import Mtlstats.Menu
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Menu.EditGoalie
|
import Mtlstats.Menu.EditGoalie
|
||||||
@@ -52,6 +55,7 @@ editC cb =
|
|||||||
EGName -> nameC
|
EGName -> nameC
|
||||||
EGYtd -> ytdMenuC
|
EGYtd -> ytdMenuC
|
||||||
EGLifetime -> lifetimeMenuC
|
EGLifetime -> lifetimeMenuC
|
||||||
|
EGDelete -> deleteC
|
||||||
EGYtdGames b -> ytdGamesC b
|
EGYtdGames b -> ytdGamesC b
|
||||||
EGYtdMins b -> ytdMinsC b
|
EGYtdMins b -> ytdMinsC b
|
||||||
EGYtdGoals b -> ytdGoalsC b
|
EGYtdGoals b -> ytdGoalsC b
|
||||||
@@ -83,6 +87,38 @@ ytdMenuC _ = menuControllerWith header editGoalieYtdMenu
|
|||||||
lifetimeMenuC :: Action () -> Controller
|
lifetimeMenuC :: Action () -> Controller
|
||||||
lifetimeMenuC _ = menuControllerWith header editGoalieLtMenu
|
lifetimeMenuC _ = menuControllerWith header editGoalieLtMenu
|
||||||
|
|
||||||
|
deleteC :: Action () -> Controller
|
||||||
|
deleteC _ = Controller
|
||||||
|
|
||||||
|
{ drawController = \s -> do
|
||||||
|
|
||||||
|
C.drawString $ let
|
||||||
|
|
||||||
|
hdr = fromMaybe [] $ do
|
||||||
|
gid <- s^.progMode.editGoalieStateL.egsSelectedGoalie
|
||||||
|
goalie <- nth gid $ s^.database.dbGoalies
|
||||||
|
Just $ "Goalie: " ++ goalieDetails goalie ++ "\n\n"
|
||||||
|
|
||||||
|
in hdr ++ "Are you sure you want to delete this goalie? (Y/N)"
|
||||||
|
|
||||||
|
return C.CursorInvisible
|
||||||
|
|
||||||
|
, handleController = \e -> do
|
||||||
|
|
||||||
|
case ynHandler e of
|
||||||
|
|
||||||
|
Just True -> do
|
||||||
|
gets (^.progMode.editGoalieStateL.egsSelectedGoalie) >>= mapM_
|
||||||
|
(\gid -> modify $ database.dbGoalies %~ dropNth gid)
|
||||||
|
modify edit
|
||||||
|
|
||||||
|
Just False -> modify $ progMode.editGoalieStateL.egsMode .~ EGMenu
|
||||||
|
Nothing -> return ()
|
||||||
|
|
||||||
|
return True
|
||||||
|
|
||||||
|
}
|
||||||
|
|
||||||
ytdGamesC :: Bool -> Action () -> Controller
|
ytdGamesC :: Bool -> Action () -> Controller
|
||||||
ytdGamesC = curry $ promptController .
|
ytdGamesC = curry $ promptController .
|
||||||
uncurry editGoalieYtdGamesPrompt
|
uncurry editGoalieYtdGamesPrompt
|
||||||
|
|||||||
@@ -21,10 +21,13 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
module Mtlstats.Control.EditPlayer (editPlayerC) where
|
module Mtlstats.Control.EditPlayer (editPlayerC) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.), (.~), (%~))
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Actions
|
||||||
|
import Mtlstats.Handlers
|
||||||
import Mtlstats.Helpers.Player
|
import Mtlstats.Helpers.Player
|
||||||
import Mtlstats.Menu
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Menu.EditPlayer
|
import Mtlstats.Menu.EditPlayer
|
||||||
@@ -45,6 +48,7 @@ editPlayerC eps
|
|||||||
EPPosition -> positionC
|
EPPosition -> positionC
|
||||||
EPYtd -> ytdC
|
EPYtd -> ytdC
|
||||||
EPLifetime -> lifetimeC
|
EPLifetime -> lifetimeC
|
||||||
|
EPDelete -> deleteC
|
||||||
EPYtdGoals b -> ytdGoalsC b
|
EPYtdGoals b -> ytdGoalsC b
|
||||||
EPYtdAssists b -> ytdAssistsC b
|
EPYtdAssists b -> ytdAssistsC b
|
||||||
EPYtdPMin -> ytdPMinC
|
EPYtdPMin -> ytdPMinC
|
||||||
@@ -74,6 +78,38 @@ ytdC _ = menuControllerWith header editPlayerYtdMenu
|
|||||||
lifetimeC :: Action () -> Controller
|
lifetimeC :: Action () -> Controller
|
||||||
lifetimeC _ = menuControllerWith header editPlayerLtMenu
|
lifetimeC _ = menuControllerWith header editPlayerLtMenu
|
||||||
|
|
||||||
|
deleteC :: Action () -> Controller
|
||||||
|
deleteC _ = Controller
|
||||||
|
|
||||||
|
{ drawController = \s -> do
|
||||||
|
|
||||||
|
C.drawString $ let
|
||||||
|
|
||||||
|
hdr = fromMaybe [] $ do
|
||||||
|
pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer
|
||||||
|
player <- nth pid $ s^.database.dbPlayers
|
||||||
|
Just $ "Player: " ++ playerDetails player ++ "\n\n"
|
||||||
|
|
||||||
|
in hdr ++ "Are you sure you want to delete this player? (Y/N)"
|
||||||
|
|
||||||
|
return C.CursorInvisible
|
||||||
|
|
||||||
|
, handleController = \e -> do
|
||||||
|
|
||||||
|
case ynHandler e of
|
||||||
|
|
||||||
|
Just True -> do
|
||||||
|
gets (^.progMode.editPlayerStateL.epsSelectedPlayer) >>= mapM_
|
||||||
|
(\pid -> modify $ database.dbPlayers %~ dropNth pid)
|
||||||
|
modify edit
|
||||||
|
|
||||||
|
Just False -> modify $ progMode.editPlayerStateL.epsMode .~ EPMenu
|
||||||
|
Nothing -> return ()
|
||||||
|
|
||||||
|
return True
|
||||||
|
|
||||||
|
}
|
||||||
|
|
||||||
ytdGoalsC :: Bool -> Action () -> Controller
|
ytdGoalsC :: Bool -> Action () -> Controller
|
||||||
ytdGoalsC batchMode callback = promptController $
|
ytdGoalsC batchMode callback = promptController $
|
||||||
editPlayerYtdGoalsPrompt batchMode callback
|
editPlayerYtdGoalsPrompt batchMode callback
|
||||||
|
|||||||
@@ -206,7 +206,7 @@ reportC = Controller
|
|||||||
C.drawString $ unlines $ slice
|
C.drawString $ unlines $ slice
|
||||||
(s^.scrollOffset)
|
(s^.scrollOffset)
|
||||||
(fromInteger $ pred rows)
|
(fromInteger $ pred rows)
|
||||||
(report (fromInteger $ pred cols) s)
|
(displayReport (fromInteger $ pred cols) s)
|
||||||
return C.CursorInvisible
|
return C.CursorInvisible
|
||||||
, handleController = \e -> do
|
, handleController = \e -> do
|
||||||
case e of
|
case e of
|
||||||
@@ -215,7 +215,7 @@ reportC = Controller
|
|||||||
C.EventSpecialKey C.KeyHome -> modify $ scrollOffset .~ 0
|
C.EventSpecialKey C.KeyHome -> modify $ scrollOffset .~ 0
|
||||||
|
|
||||||
C.EventCharacter '\n' -> do
|
C.EventCharacter '\n' -> do
|
||||||
get >>= liftIO . writeFile reportFilename . unlines . report reportCols
|
get >>= liftIO . writeFile reportFilename . exportReport reportCols
|
||||||
modify backHome
|
modify backHome
|
||||||
|
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
|
|||||||
@@ -45,7 +45,6 @@ import qualified UI.NCurses as C
|
|||||||
import Mtlstats.Actions
|
import Mtlstats.Actions
|
||||||
import qualified Mtlstats.Actions.NewGame.GoalieInput as GI
|
import qualified Mtlstats.Actions.NewGame.GoalieInput as GI
|
||||||
import Mtlstats.Actions.EditStandings
|
import Mtlstats.Actions.EditStandings
|
||||||
import Mtlstats.Config
|
|
||||||
import Mtlstats.Format
|
import Mtlstats.Format
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Types.Menu
|
import Mtlstats.Types.Menu
|
||||||
@@ -115,7 +114,7 @@ mainMenu = Menu "MASTER MENU" True
|
|||||||
, MenuItem 'C' "EDIT MENU" $
|
, MenuItem 'C' "EDIT MENU" $
|
||||||
modify edit >> return True
|
modify edit >> return True
|
||||||
, MenuItem 'E' "EXIT" $
|
, MenuItem 'E' "EXIT" $
|
||||||
saveDatabase dbFname >> return False
|
saveDatabase >> return False
|
||||||
]
|
]
|
||||||
|
|
||||||
-- | The new season menu
|
-- | The new season menu
|
||||||
|
|||||||
@@ -44,6 +44,7 @@ editGoalieMenu = Menu "EDIT GOALTENDER" () $ map
|
|||||||
, ( 'D', "ACTIVE FLAG", toggleActive )
|
, ( 'D', "ACTIVE FLAG", toggleActive )
|
||||||
, ( 'E', "YTD STATS", set EGYtd )
|
, ( 'E', "YTD STATS", set EGYtd )
|
||||||
, ( 'F', "LIFETIME STATS", set EGLifetime )
|
, ( 'F', "LIFETIME STATS", set EGLifetime )
|
||||||
|
, ( 'G', "DELETE RECORD", set EGDelete )
|
||||||
, ( 'R', "RETURN TO EDIT MENU", edit )
|
, ( 'R', "RETURN TO EDIT MENU", edit )
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|||||||
@@ -45,6 +45,7 @@ editPlayerMenu = Menu "EDIT PLAYER" () $ map
|
|||||||
, ( 'E', "ACTIVE FLAG", toggleActive )
|
, ( 'E', "ACTIVE FLAG", toggleActive )
|
||||||
, ( 'F', "YTD STATS", set EPYtd )
|
, ( 'F', "YTD STATS", set EPYtd )
|
||||||
, ( 'G', "LIFETIME STATS", set EPLifetime )
|
, ( 'G', "LIFETIME STATS", set EPLifetime )
|
||||||
|
, ( 'H', "DELETE RECORD", set EPDelete )
|
||||||
, ( 'R', "RETURN TO EDIT MENU", edit )
|
, ( 'R', "RETURN TO EDIT MENU", edit )
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|||||||
@@ -32,8 +32,10 @@ module Mtlstats.Prompt (
|
|||||||
namePrompt,
|
namePrompt,
|
||||||
numPrompt,
|
numPrompt,
|
||||||
numPromptWithFallback,
|
numPromptWithFallback,
|
||||||
|
dbNamePrompt,
|
||||||
selectPrompt,
|
selectPrompt,
|
||||||
-- * Individual prompts
|
-- * Individual prompts
|
||||||
|
getDBPrompt,
|
||||||
newSeasonPrompt,
|
newSeasonPrompt,
|
||||||
playerNumPrompt,
|
playerNumPrompt,
|
||||||
playerNamePrompt,
|
playerNamePrompt,
|
||||||
@@ -41,7 +43,9 @@ module Mtlstats.Prompt (
|
|||||||
goalieNumPrompt,
|
goalieNumPrompt,
|
||||||
goalieNamePrompt,
|
goalieNamePrompt,
|
||||||
selectPlayerPrompt,
|
selectPlayerPrompt,
|
||||||
|
selectActivePlayerPrompt,
|
||||||
selectGoaliePrompt,
|
selectGoaliePrompt,
|
||||||
|
selectActiveGoaliePrompt,
|
||||||
selectPositionPrompt,
|
selectPositionPrompt,
|
||||||
playerToEditPrompt
|
playerToEditPrompt
|
||||||
) where
|
) where
|
||||||
@@ -168,24 +172,30 @@ numPromptWithFallback pStr fallback act = Prompt
|
|||||||
, promptSpecialKey = const $ return ()
|
, promptSpecialKey = const $ return ()
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Prompts for a database name
|
||||||
|
dbNamePrompt
|
||||||
|
:: String
|
||||||
|
-- ^ The prompt string
|
||||||
|
-> (String -> Action ())
|
||||||
|
-- ^ The callback to pass the result to
|
||||||
|
-> Prompt
|
||||||
|
dbNamePrompt pStr act = (strPrompt pStr act)
|
||||||
|
{ promptProcessChar = \ch -> if isAlphaNum ch || ch == '-'
|
||||||
|
then (++[toUpper ch])
|
||||||
|
else id
|
||||||
|
}
|
||||||
|
|
||||||
-- | Prompts the user for a filename to save a backup of the database
|
-- | Prompts the user for a filename to save a backup of the database
|
||||||
-- to
|
-- to
|
||||||
newSeasonPrompt :: Prompt
|
newSeasonPrompt :: Prompt
|
||||||
newSeasonPrompt = prompt
|
newSeasonPrompt = dbNamePrompt "Filename for new season: " $ \fn ->
|
||||||
{ promptProcessChar = \ch str -> if validChar ch
|
if null fn
|
||||||
then str ++ [toUpper ch]
|
then modify backHome
|
||||||
else str
|
else do
|
||||||
}
|
saveDatabase
|
||||||
where
|
modify
|
||||||
|
$ (dbName .~ fn)
|
||||||
prompt = strPrompt "Filename to save database: " $ \fn ->
|
. (progMode .~ NewSeason True)
|
||||||
if null fn
|
|
||||||
then modify backHome
|
|
||||||
else do
|
|
||||||
saveDatabase $ fn ++ ".json"
|
|
||||||
modify $ progMode .~ NewSeason True
|
|
||||||
|
|
||||||
validChar = (||) <$> isAlphaNum <*> (=='-')
|
|
||||||
|
|
||||||
-- | Builds a selection prompt
|
-- | Builds a selection prompt
|
||||||
selectPrompt :: SelectParams a -> Prompt
|
selectPrompt :: SelectParams a -> Prompt
|
||||||
@@ -224,6 +234,12 @@ selectPrompt params = Prompt
|
|||||||
_ -> return ()
|
_ -> return ()
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Prompts for the database to load
|
||||||
|
getDBPrompt :: Prompt
|
||||||
|
getDBPrompt = dbNamePrompt "Season database to load: " $ \fn -> do
|
||||||
|
modify $ dbName .~ fn
|
||||||
|
loadDatabase
|
||||||
|
|
||||||
-- | Prompts for a new player's number
|
-- | Prompts for a new player's number
|
||||||
playerNumPrompt :: Prompt
|
playerNumPrompt :: Prompt
|
||||||
playerNumPrompt = numPrompt "Player number: " $
|
playerNumPrompt = numPrompt "Player number: " $
|
||||||
@@ -249,18 +265,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
|
||||||
@@ -278,18 +297,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
|
||||||
@@ -307,6 +349,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
|
||||||
|
|||||||
@@ -76,7 +76,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 +90,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 +104,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
|
||||||
|
|||||||
@@ -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
|
||||||
|
|||||||
@@ -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 (displayReport, exportReport, gameDate) where
|
||||||
|
|
||||||
import Data.List (sortOn)
|
import Data.List (sortOn)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
@@ -34,21 +34,37 @@ import Mtlstats.Helpers.Player
|
|||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Util
|
import Mtlstats.Util
|
||||||
|
|
||||||
-- | Generates the report
|
-- | Generates the report displayed on screen
|
||||||
report
|
displayReport
|
||||||
:: Int
|
:: Int
|
||||||
-- ^ The number of columns for the report
|
-- ^ The number of columns for the report
|
||||||
-> ProgState
|
-> ProgState
|
||||||
-- ^ The program state
|
-- ^ The program state
|
||||||
-> [String]
|
-> [String]
|
||||||
|
displayReport width s
|
||||||
|
= report width s
|
||||||
|
++ [""]
|
||||||
|
++ lifetimeStatsReport width s
|
||||||
|
|
||||||
|
-- | Generates the report to be exported to file
|
||||||
|
exportReport
|
||||||
|
:: Int
|
||||||
|
-- ^ The number of columns in the report
|
||||||
|
-> ProgState
|
||||||
|
-- ^ The program state
|
||||||
|
-> String
|
||||||
|
exportReport width s
|
||||||
|
= unlines (report width s)
|
||||||
|
++ "\f"
|
||||||
|
++ unlines (lifetimeStatsReport width s)
|
||||||
|
|
||||||
|
report :: Int -> ProgState -> [String]
|
||||||
report width s
|
report width s
|
||||||
= standingsReport width s
|
= standingsReport width s
|
||||||
++ [""]
|
++ [""]
|
||||||
++ gameStatsReport width s
|
++ gameStatsReport width s
|
||||||
++ [""]
|
++ [""]
|
||||||
++ yearToDateStatsReport width s
|
++ yearToDateStatsReport width s
|
||||||
++ [""]
|
|
||||||
++ lifetimeStatsReport width s
|
|
||||||
|
|
||||||
standingsReport :: Int -> ProgState -> [String]
|
standingsReport :: Int -> ProgState -> [String]
|
||||||
standingsReport width s = fromMaybe [] $ do
|
standingsReport width s = fromMaybe [] $ do
|
||||||
|
|||||||
@@ -50,6 +50,7 @@ module Mtlstats.Types (
|
|||||||
-- ** ProgState Lenses
|
-- ** ProgState Lenses
|
||||||
database,
|
database,
|
||||||
progMode,
|
progMode,
|
||||||
|
dbName,
|
||||||
inputBuffer,
|
inputBuffer,
|
||||||
scrollOffset,
|
scrollOffset,
|
||||||
-- ** ProgMode Lenses
|
-- ** ProgMode Lenses
|
||||||
@@ -175,6 +176,7 @@ module Mtlstats.Types (
|
|||||||
addGameStats,
|
addGameStats,
|
||||||
-- ** Player Helpers
|
-- ** Player Helpers
|
||||||
playerSearch,
|
playerSearch,
|
||||||
|
activePlayerSearch,
|
||||||
playerSearchExact,
|
playerSearchExact,
|
||||||
modifyPlayer,
|
modifyPlayer,
|
||||||
playerSummary,
|
playerSummary,
|
||||||
@@ -184,6 +186,7 @@ module Mtlstats.Types (
|
|||||||
addPlayerStats,
|
addPlayerStats,
|
||||||
-- ** Goalie Helpers
|
-- ** Goalie Helpers
|
||||||
goalieSearch,
|
goalieSearch,
|
||||||
|
activeGoalieSearch,
|
||||||
goalieSearchExact,
|
goalieSearchExact,
|
||||||
goalieSummary,
|
goalieSummary,
|
||||||
goalieIsActive,
|
goalieIsActive,
|
||||||
@@ -233,6 +236,8 @@ data ProgState = ProgState
|
|||||||
-- ^ The data to be saved
|
-- ^ The data to be saved
|
||||||
, _progMode :: ProgMode
|
, _progMode :: ProgMode
|
||||||
-- ^ The program's mode
|
-- ^ The program's mode
|
||||||
|
, _dbName :: String
|
||||||
|
-- ^ The name of the database file
|
||||||
, _inputBuffer :: String
|
, _inputBuffer :: String
|
||||||
-- ^ Buffer for user input
|
-- ^ Buffer for user input
|
||||||
, _scrollOffset :: Int
|
, _scrollOffset :: Int
|
||||||
@@ -375,6 +380,7 @@ data EditPlayerMode
|
|||||||
| EPPosition
|
| EPPosition
|
||||||
| EPYtd
|
| EPYtd
|
||||||
| EPLifetime
|
| EPLifetime
|
||||||
|
| EPDelete
|
||||||
| EPYtdGoals Bool
|
| EPYtdGoals Bool
|
||||||
| EPYtdAssists Bool
|
| EPYtdAssists Bool
|
||||||
| EPYtdPMin
|
| EPYtdPMin
|
||||||
@@ -400,6 +406,7 @@ data EditGoalieMode
|
|||||||
| EGName
|
| EGName
|
||||||
| EGYtd
|
| EGYtd
|
||||||
| EGLifetime
|
| EGLifetime
|
||||||
|
| EGDelete
|
||||||
| EGYtdGames Bool
|
| EGYtdGames Bool
|
||||||
| EGYtdMins Bool
|
| EGYtdMins Bool
|
||||||
| EGYtdGoals Bool
|
| EGYtdGoals Bool
|
||||||
@@ -781,6 +788,7 @@ newProgState :: ProgState
|
|||||||
newProgState = ProgState
|
newProgState = ProgState
|
||||||
{ _database = newDatabase
|
{ _database = newDatabase
|
||||||
, _progMode = TitleScreen
|
, _progMode = TitleScreen
|
||||||
|
, _dbName = ""
|
||||||
, _inputBuffer = ""
|
, _inputBuffer = ""
|
||||||
, _scrollOffset = 0
|
, _scrollOffset = 0
|
||||||
}
|
}
|
||||||
@@ -997,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
|
||||||
@@ -1005,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
|
||||||
@@ -1062,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
|
||||||
@@ -1070,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
|
||||||
|
|||||||
@@ -22,6 +22,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
module Mtlstats.Util
|
module Mtlstats.Util
|
||||||
( nth
|
( nth
|
||||||
, modifyNth
|
, modifyNth
|
||||||
|
, dropNth
|
||||||
, updateMap
|
, updateMap
|
||||||
, slice
|
, slice
|
||||||
, capitalizeName
|
, capitalizeName
|
||||||
@@ -56,6 +57,18 @@ modifyNth n f = zipWith
|
|||||||
(\i x -> if i == n then f x else x)
|
(\i x -> if i == n then f x else x)
|
||||||
[0..]
|
[0..]
|
||||||
|
|
||||||
|
-- | Attempt to drop the nth element from a list
|
||||||
|
dropNth
|
||||||
|
:: Int
|
||||||
|
-- ^ The index of the element to drop
|
||||||
|
-> [a]
|
||||||
|
-- ^ The list to be modified
|
||||||
|
-> [a]
|
||||||
|
-- ^ The modified list
|
||||||
|
dropNth n = foldr
|
||||||
|
(\(i, x) acc -> if i == n then acc else x : acc)
|
||||||
|
[] . zip [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
|
||||||
updateMap
|
updateMap
|
||||||
|
|||||||
@@ -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
|
||||||
|
|||||||
@@ -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
|
||||||
|
|||||||
@@ -30,6 +30,7 @@ spec :: Spec
|
|||||||
spec = describe "Mtlstats.Util" $ do
|
spec = describe "Mtlstats.Util" $ do
|
||||||
nthSpec
|
nthSpec
|
||||||
modifyNthSpec
|
modifyNthSpec
|
||||||
|
dropNthSpec
|
||||||
updateMapSpec
|
updateMapSpec
|
||||||
sliceSpec
|
sliceSpec
|
||||||
capitalizeNameSpec
|
capitalizeNameSpec
|
||||||
@@ -64,6 +65,20 @@ modifyNthSpec = describe "modifyNth" $ do
|
|||||||
it "should not modify the value" $
|
it "should not modify the value" $
|
||||||
modifyNth (-1) succ list `shouldBe` [1, 2, 3]
|
modifyNth (-1) succ list `shouldBe` [1, 2, 3]
|
||||||
|
|
||||||
|
dropNthSpec :: Spec
|
||||||
|
dropNthSpec = describe "dropNth" $ mapM_
|
||||||
|
|
||||||
|
(\(label, n, expected) ->
|
||||||
|
context label $
|
||||||
|
it ("should be " ++ show expected) $
|
||||||
|
dropNth n list `shouldBe` expected)
|
||||||
|
|
||||||
|
[ ( "out of bounds", 1, ["foo", "baz"] )
|
||||||
|
, ( "in bounds", 3, list )
|
||||||
|
]
|
||||||
|
|
||||||
|
where list = ["foo", "bar", "baz"]
|
||||||
|
|
||||||
updateMapSpec :: Spec
|
updateMapSpec :: Spec
|
||||||
updateMapSpec = describe "updateMap" $ do
|
updateMapSpec = describe "updateMap" $ do
|
||||||
let
|
let
|
||||||
|
|||||||
Reference in New Issue
Block a user