2019-08-24 16:23:56 -04:00
|
|
|
{- |
|
|
|
|
|
|
|
|
mtlstats
|
|
|
|
Copyright (C) 2019 Rhéal Lamothe
|
|
|
|
<rheal.lamothe@gmail.com>
|
|
|
|
|
|
|
|
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 <https://www.gnu.org/licenses/>.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2019-09-19 04:35:01 -04:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
|
2019-08-24 16:23:56 -04:00
|
|
|
module Mtlstats.Prompt (
|
|
|
|
-- * Prompt Functions
|
|
|
|
drawPrompt,
|
|
|
|
promptHandler,
|
2019-11-04 00:51:50 -05:00
|
|
|
promptControllerWith,
|
|
|
|
promptController,
|
2019-08-24 21:15:50 -04:00
|
|
|
strPrompt,
|
2019-08-24 19:02:29 -04:00
|
|
|
numPrompt,
|
2019-10-30 16:57:08 -04:00
|
|
|
selectPrompt,
|
2019-08-24 19:02:29 -04:00
|
|
|
-- * Individual prompts
|
2019-08-31 11:28:09 -04:00
|
|
|
gameYearPrompt,
|
2019-08-31 12:42:11 -04:00
|
|
|
gameDayPrompt,
|
2019-08-25 10:04:37 -04:00
|
|
|
otherTeamPrompt,
|
2019-08-24 20:14:49 -04:00
|
|
|
homeScorePrompt,
|
2019-09-09 13:04:39 -04:00
|
|
|
awayScorePrompt,
|
2019-09-09 22:50:44 -04:00
|
|
|
playerNumPrompt,
|
|
|
|
playerNamePrompt,
|
2019-09-19 04:35:01 -04:00
|
|
|
playerPosPrompt,
|
|
|
|
selectPlayerPrompt,
|
2019-10-30 00:29:33 -04:00
|
|
|
selectGoaliePrompt,
|
2019-09-19 05:50:48 -04:00
|
|
|
recordGoalPrompt,
|
2019-10-09 01:24:55 -04:00
|
|
|
recordAssistPrompt,
|
2019-10-09 22:15:40 -04:00
|
|
|
pMinPlayerPrompt,
|
2019-10-24 15:53:24 -04:00
|
|
|
assignPMinsPrompt,
|
2019-10-25 00:45:39 -04:00
|
|
|
goalieNumPrompt,
|
2019-10-29 02:51:20 -04:00
|
|
|
goalieNamePrompt,
|
2019-10-30 23:41:55 -04:00
|
|
|
selectGameGoaliePrompt,
|
2019-10-31 00:24:54 -04:00
|
|
|
goalieMinsPlayedPrompt,
|
2019-11-01 03:05:40 -04:00
|
|
|
goalsAllowedPrompt,
|
|
|
|
playerToEditPrompt
|
2019-08-24 16:23:56 -04:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Control.Monad (when)
|
2019-10-30 16:57:08 -04:00
|
|
|
import Control.Monad.Extra (whenJust)
|
2019-08-24 16:23:56 -04:00
|
|
|
import Control.Monad.Trans.State (gets, modify)
|
|
|
|
import Data.Char (isDigit, toUpper)
|
|
|
|
import Data.Foldable (forM_)
|
2019-10-31 01:21:21 -04:00
|
|
|
import Data.Maybe (fromMaybe)
|
2019-09-19 05:50:48 -04:00
|
|
|
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
|
2019-08-24 16:23:56 -04:00
|
|
|
import Lens.Micro.Extras (view)
|
|
|
|
import Text.Read (readMaybe)
|
|
|
|
import qualified UI.NCurses as C
|
|
|
|
|
|
|
|
import Mtlstats.Actions
|
2019-09-19 06:34:03 -04:00
|
|
|
import Mtlstats.Config
|
2019-09-19 05:50:48 -04:00
|
|
|
import Mtlstats.Format
|
2019-08-24 16:23:56 -04:00
|
|
|
import Mtlstats.Types
|
2019-09-19 04:35:01 -04:00
|
|
|
import Mtlstats.Util
|
2019-08-24 16:23:56 -04:00
|
|
|
|
|
|
|
-- | Draws the prompt to the screen
|
|
|
|
drawPrompt :: Prompt -> ProgState -> C.Update C.CursorMode
|
|
|
|
drawPrompt p s = do
|
|
|
|
promptDrawer p s
|
|
|
|
return C.CursorVisible
|
|
|
|
|
|
|
|
-- | Event handler for a prompt
|
|
|
|
promptHandler :: Prompt -> C.Event -> Action ()
|
|
|
|
promptHandler p (C.EventCharacter '\n') = do
|
|
|
|
val <- gets $ view inputBuffer
|
|
|
|
modify $ inputBuffer .~ ""
|
|
|
|
promptAction p val
|
|
|
|
promptHandler p (C.EventCharacter c) = let
|
|
|
|
c' = toUpper c
|
|
|
|
in when (promptCharCheck p c') $
|
|
|
|
modify $ addChar c'
|
|
|
|
promptHandler _ (C.EventSpecialKey C.KeyBackspace) =
|
|
|
|
modify removeChar
|
2019-09-19 02:45:50 -04:00
|
|
|
promptHandler p (C.EventSpecialKey k) =
|
|
|
|
promptSpecialKey p k
|
2019-08-24 16:23:56 -04:00
|
|
|
promptHandler _ _ = return ()
|
|
|
|
|
2019-11-04 00:51:50 -05:00
|
|
|
-- | Builds a controller out of a prompt with a header
|
|
|
|
promptControllerWith
|
|
|
|
:: (ProgState -> C.Update ())
|
|
|
|
-- ^ The header
|
|
|
|
-> Prompt
|
|
|
|
-- ^ The prompt to use
|
|
|
|
-> Controller
|
|
|
|
-- ^ The resulting controller
|
|
|
|
promptControllerWith header prompt = Controller
|
|
|
|
{ drawController = \s -> do
|
|
|
|
header s
|
|
|
|
drawPrompt prompt s
|
|
|
|
, handleController = \e -> do
|
|
|
|
promptHandler prompt e
|
|
|
|
return True
|
|
|
|
}
|
|
|
|
|
|
|
|
-- | Builds a controller out of a prompt
|
|
|
|
promptController
|
|
|
|
:: Prompt
|
|
|
|
-- ^ The prompt to use
|
|
|
|
-> Controller
|
|
|
|
-- ^ The resulting controller
|
|
|
|
promptController = promptControllerWith (const $ return ())
|
|
|
|
|
2019-08-24 21:15:50 -04:00
|
|
|
-- | Builds a string prompt
|
|
|
|
strPrompt
|
|
|
|
:: String
|
|
|
|
-- ^ The prompt string
|
|
|
|
-> (String -> Action ())
|
|
|
|
-- ^ The callback function for the result
|
|
|
|
-> Prompt
|
|
|
|
strPrompt pStr act = Prompt
|
2019-09-19 02:45:50 -04:00
|
|
|
{ promptDrawer = drawSimplePrompt pStr
|
|
|
|
, promptCharCheck = const True
|
|
|
|
, promptAction = act
|
|
|
|
, promptSpecialKey = const $ return ()
|
2019-08-24 21:15:50 -04:00
|
|
|
}
|
|
|
|
|
2019-08-24 16:23:56 -04:00
|
|
|
-- | Builds a numeric prompt
|
|
|
|
numPrompt
|
|
|
|
:: String
|
|
|
|
-- ^ The prompt string
|
|
|
|
-> (Int -> Action ())
|
|
|
|
-- ^ The callback function for the result
|
|
|
|
-> Prompt
|
|
|
|
numPrompt pStr act = Prompt
|
2019-09-19 02:45:50 -04:00
|
|
|
{ promptDrawer = drawSimplePrompt pStr
|
|
|
|
, promptCharCheck = isDigit
|
|
|
|
, promptAction = \inStr -> forM_ (readMaybe inStr) act
|
|
|
|
, promptSpecialKey = const $ return ()
|
2019-08-24 16:23:56 -04:00
|
|
|
}
|
2019-08-24 19:02:29 -04:00
|
|
|
|
2019-10-30 16:57:08 -04:00
|
|
|
-- | Builds a selection prompt
|
|
|
|
selectPrompt :: SelectParams a -> Prompt
|
|
|
|
selectPrompt params = Prompt
|
|
|
|
{ promptDrawer = \s -> do
|
|
|
|
let sStr = s^.inputBuffer
|
|
|
|
C.drawString $ spPrompt params ++ sStr
|
|
|
|
(row, col) <- C.cursorPosition
|
|
|
|
C.drawString $ "\n\n" ++ spSearchHeader params ++ "\n"
|
|
|
|
let results = zip [1..maxFunKeys] $ spSearch params sStr (s^.database)
|
|
|
|
C.drawString $ unlines $ map
|
|
|
|
(\(n, (_, x)) -> let
|
|
|
|
desc = spElemDesc params x
|
|
|
|
in "F" ++ show n ++ ") " ++ desc)
|
|
|
|
results
|
|
|
|
C.moveCursor row col
|
|
|
|
, promptCharCheck = const True
|
|
|
|
, promptAction = \sStr -> if null sStr
|
|
|
|
then spCallback params Nothing
|
|
|
|
else do
|
|
|
|
db <- gets (^.database)
|
|
|
|
case spSearchExact params sStr db of
|
|
|
|
Nothing -> spNotFound params sStr
|
|
|
|
Just n -> spCallback params $ Just n
|
|
|
|
, promptSpecialKey = \case
|
|
|
|
C.KeyFunction rawK -> do
|
|
|
|
sStr <- gets (^.inputBuffer)
|
|
|
|
db <- gets (^.database)
|
|
|
|
let
|
|
|
|
n = pred $ fromInteger rawK
|
|
|
|
results = spSearch params sStr db
|
|
|
|
when (n < maxFunKeys) $
|
|
|
|
whenJust (nth n results) $ \(n, _) -> do
|
|
|
|
modify $ inputBuffer .~ ""
|
|
|
|
spCallback params $ Just n
|
|
|
|
_ -> return ()
|
|
|
|
}
|
|
|
|
|
2019-08-31 11:28:09 -04:00
|
|
|
-- | Prompts for the game year
|
|
|
|
gameYearPrompt :: Prompt
|
|
|
|
gameYearPrompt = numPrompt "Game year: " $
|
|
|
|
modify . (progMode.gameStateL.gameYear ?~)
|
|
|
|
|
2019-08-31 12:42:11 -04:00
|
|
|
-- | Prompts for the day of the month the game took place
|
|
|
|
gameDayPrompt :: Prompt
|
|
|
|
gameDayPrompt = numPrompt "Day of month: " $
|
|
|
|
modify . (progMode.gameStateL.gameDay ?~)
|
|
|
|
|
2019-08-31 11:24:55 -04:00
|
|
|
-- | Prompts for the other team name
|
2019-08-25 10:04:37 -04:00
|
|
|
otherTeamPrompt :: Prompt
|
|
|
|
otherTeamPrompt = strPrompt "Other team: " $
|
2019-08-31 11:27:02 -04:00
|
|
|
modify . (progMode.gameStateL.otherTeam .~)
|
2019-08-25 10:04:37 -04:00
|
|
|
|
2019-08-31 11:24:55 -04:00
|
|
|
-- | Prompts for the home score
|
2019-08-24 19:02:29 -04:00
|
|
|
homeScorePrompt :: Prompt
|
|
|
|
homeScorePrompt = numPrompt "Home score: " $
|
2019-08-31 11:27:02 -04:00
|
|
|
modify . (progMode.gameStateL.homeScore ?~)
|
2019-08-24 20:14:49 -04:00
|
|
|
|
2019-08-31 11:24:55 -04:00
|
|
|
-- | Prompts for the away score
|
2019-08-24 20:14:49 -04:00
|
|
|
awayScorePrompt :: Prompt
|
|
|
|
awayScorePrompt = numPrompt "Away score: " $
|
2019-08-31 11:27:02 -04:00
|
|
|
modify . (progMode.gameStateL.awayScore ?~)
|
2019-08-24 21:15:50 -04:00
|
|
|
|
2019-09-09 13:04:39 -04:00
|
|
|
-- | Prompts for a new player's number
|
|
|
|
playerNumPrompt :: Prompt
|
|
|
|
playerNumPrompt = numPrompt "Player number: " $
|
|
|
|
modify . (progMode.createPlayerStateL.cpsNumber ?~)
|
|
|
|
|
2019-09-09 22:50:44 -04:00
|
|
|
-- | Prompts for a new player's name
|
|
|
|
playerNamePrompt :: Prompt
|
|
|
|
playerNamePrompt = strPrompt "Player name: " $
|
|
|
|
modify . (progMode.createPlayerStateL.cpsName .~)
|
|
|
|
|
2019-09-09 22:57:36 -04:00
|
|
|
-- | Prompts for a new player's position
|
|
|
|
playerPosPrompt :: Prompt
|
|
|
|
playerPosPrompt = strPrompt "Player position: " $
|
|
|
|
modify . (progMode.createPlayerStateL.cpsPosition .~)
|
|
|
|
|
2019-09-19 04:35:01 -04:00
|
|
|
-- | Selects a player (creating one if necessary)
|
|
|
|
selectPlayerPrompt
|
|
|
|
:: String
|
|
|
|
-- ^ The prompt string
|
|
|
|
-> (Maybe Int -> Action ())
|
|
|
|
-- ^ The callback to run (takes the index number of the payer as
|
|
|
|
-- input)
|
|
|
|
-> Prompt
|
2019-10-30 17:29:47 -04:00
|
|
|
selectPlayerPrompt pStr callback = selectPrompt SelectParams
|
|
|
|
{ spPrompt = pStr
|
|
|
|
, spSearchHeader = "Player select:"
|
|
|
|
, spSearch = \sStr db -> playerSearch sStr (db^.dbPlayers)
|
|
|
|
, spSearchExact = \sStr db -> fst <$> playerSearchExact sStr (db^.dbPlayers)
|
|
|
|
, spElemDesc = playerSummary
|
|
|
|
, spCallback = callback
|
|
|
|
, spNotFound = \sStr -> do
|
|
|
|
mode <- gets (^.progMode)
|
|
|
|
let
|
|
|
|
cps = newCreatePlayerState
|
|
|
|
& cpsName .~ sStr
|
|
|
|
& cpsSuccessCallback .~ do
|
|
|
|
modify $ progMode .~ mode
|
|
|
|
index <- pred . length <$> gets (^.database.dbPlayers)
|
|
|
|
callback $ Just index
|
|
|
|
& cpsFailureCallback .~ modify (progMode .~ mode)
|
|
|
|
modify $ progMode .~ CreatePlayer cps
|
2019-09-19 04:35:01 -04:00
|
|
|
}
|
|
|
|
|
2019-10-30 00:29:33 -04:00
|
|
|
-- | 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
|
2019-10-30 21:57:31 -04:00
|
|
|
selectGoaliePrompt pStr callback = selectPrompt SelectParams
|
|
|
|
{ spPrompt = pStr
|
|
|
|
, spSearchHeader = "Goalie select:"
|
|
|
|
, spSearch = \sStr db -> goalieSearch sStr (db^.dbGoalies)
|
|
|
|
, spSearchExact = \sStr db -> fst <$> goalieSearchExact sStr (db^.dbGoalies)
|
|
|
|
, spElemDesc = goalieSummary
|
|
|
|
, spCallback = callback
|
|
|
|
, spNotFound = \sStr -> do
|
|
|
|
mode <- gets (^.progMode)
|
|
|
|
let
|
|
|
|
cgs = newCreateGoalieState
|
|
|
|
& cgsName .~ sStr
|
|
|
|
& cgsSuccessCallback .~ do
|
|
|
|
modify $ progMode .~ mode
|
|
|
|
index <- pred . length <$> gets (^.database.dbGoalies)
|
|
|
|
callback $ Just index
|
|
|
|
& cgsFailureCallback .~ modify (progMode .~ mode)
|
|
|
|
modify $ progMode .~ CreateGoalie cgs
|
|
|
|
}
|
2019-10-30 00:29:33 -04:00
|
|
|
|
2019-09-19 05:50:48 -04:00
|
|
|
-- | Prompts for the player who scored the goal
|
|
|
|
recordGoalPrompt
|
|
|
|
:: Int
|
|
|
|
-- ^ The game number
|
|
|
|
-> Int
|
|
|
|
-- ^ The goal number
|
|
|
|
-> Prompt
|
|
|
|
recordGoalPrompt game goal = selectPlayerPrompt
|
2019-09-26 01:23:34 -04:00
|
|
|
( "*** GAME " ++ padNum 2 game ++ " ***\n"
|
|
|
|
++ "Who scored goal number " ++ show goal ++ "? "
|
2019-09-28 02:09:11 -04:00
|
|
|
) $ modify . (progMode.gameStateL.goalBy .~)
|
2019-09-19 05:50:48 -04:00
|
|
|
|
2019-09-26 01:23:34 -04:00
|
|
|
-- | Prompts for a player who assisted the goal
|
|
|
|
recordAssistPrompt
|
|
|
|
:: Int
|
|
|
|
-- ^ The game number
|
|
|
|
-> Int
|
|
|
|
-- ^ The goal nuber
|
|
|
|
-> Int
|
|
|
|
-- ^ The assist number
|
|
|
|
-> Prompt
|
|
|
|
recordAssistPrompt game goal assist = selectPlayerPrompt
|
|
|
|
( "*** GAME " ++ padNum 2 game ++ " ***\n"
|
|
|
|
++ "Goal: " ++ show goal ++ "\n"
|
|
|
|
++ "Assist #" ++ show assist ++ ": "
|
|
|
|
) $ \case
|
2019-10-01 00:56:23 -04:00
|
|
|
Nothing -> modify $ progMode.gameStateL.confirmGoalDataFlag .~ True
|
2019-09-28 02:09:11 -04:00
|
|
|
Just n -> do
|
|
|
|
modify $ progMode.gameStateL.assistsBy %~ (++[n])
|
|
|
|
nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy)
|
|
|
|
when (nAssists >= maxAssists) $
|
2019-10-01 00:56:23 -04:00
|
|
|
modify $ progMode.gameStateL.confirmGoalDataFlag .~ True
|
2019-09-26 01:23:34 -04:00
|
|
|
|
2019-10-25 00:48:28 -04:00
|
|
|
-- | Prompts for the player to assign penalty minutes to
|
2019-10-09 01:24:55 -04:00
|
|
|
pMinPlayerPrompt :: Prompt
|
2019-10-09 21:54:55 -04:00
|
|
|
pMinPlayerPrompt = selectPlayerPrompt
|
|
|
|
"Assign penalty minutes to: " $
|
|
|
|
\case
|
|
|
|
Nothing -> modify $ progMode.gameStateL.pMinsRecorded .~ True
|
|
|
|
Just n -> modify $ progMode.gameStateL.selectedPlayer ?~ n
|
2019-10-09 01:24:55 -04:00
|
|
|
|
2019-10-25 00:48:28 -04:00
|
|
|
-- | Prompts for the number of penalty mintues to assign to the player
|
2019-10-09 22:15:40 -04:00
|
|
|
assignPMinsPrompt :: Prompt
|
2019-10-09 22:32:14 -04:00
|
|
|
assignPMinsPrompt = numPrompt "Penalty minutes: " $
|
|
|
|
modify . assignPMins
|
2019-10-09 22:15:40 -04:00
|
|
|
|
2019-10-25 00:48:28 -04:00
|
|
|
-- | Prompts tor the goalie's number
|
2019-10-24 15:53:24 -04:00
|
|
|
goalieNumPrompt :: Prompt
|
2019-10-25 00:11:26 -04:00
|
|
|
goalieNumPrompt = numPrompt "Goalie number: " $
|
|
|
|
modify . (progMode.createGoalieStateL.cgsNumber ?~)
|
2019-10-24 15:53:24 -04:00
|
|
|
|
2019-10-25 00:48:28 -04:00
|
|
|
-- | Prompts for the goalie's name
|
2019-10-25 00:45:39 -04:00
|
|
|
goalieNamePrompt :: Prompt
|
|
|
|
goalieNamePrompt = strPrompt "Goalie name: " $
|
|
|
|
modify . (progMode.createGoalieStateL.cgsName .~)
|
|
|
|
|
2019-10-29 02:51:20 -04:00
|
|
|
-- | Prompts for a goalie who played in the game
|
|
|
|
selectGameGoaliePrompt :: Prompt
|
2019-10-30 21:57:31 -04:00
|
|
|
selectGameGoaliePrompt = selectGoaliePrompt "Which goalie played this game: " $
|
2019-10-30 00:29:33 -04:00
|
|
|
\case
|
|
|
|
Nothing -> modify $ progMode.gameStateL.goaliesRecorded .~ True
|
|
|
|
Just n -> modify $ progMode.gameStateL.gameSelectedGoalie ?~ n
|
2019-10-29 02:51:20 -04:00
|
|
|
|
2019-10-30 23:41:55 -04:00
|
|
|
-- | Prompts for the number of minutes the goalie has played
|
|
|
|
goalieMinsPlayedPrompt :: Prompt
|
2019-10-30 23:58:51 -04:00
|
|
|
goalieMinsPlayedPrompt = numPrompt "Minutes played: " $
|
|
|
|
modify . (progMode.gameStateL.goalieMinsPlayed ?~)
|
2019-10-30 23:41:55 -04:00
|
|
|
|
2019-10-31 00:24:54 -04:00
|
|
|
-- | Prompts for the number of goals the goalie allowed
|
|
|
|
goalsAllowedPrompt :: Prompt
|
2019-10-31 01:21:21 -04:00
|
|
|
goalsAllowedPrompt = numPrompt "Goals allowed: " $ \n -> do
|
|
|
|
modify (progMode.gameStateL.goalsAllowed ?~ n)
|
|
|
|
mins <- fromMaybe 0 <$> gets (^.progMode.gameStateL.goalieMinsPlayed)
|
|
|
|
when (mins >= gameLength) $
|
|
|
|
modify $ progMode.gameStateL.goaliesRecorded .~ True
|
|
|
|
modify recordGoalieStats
|
2019-10-31 00:24:54 -04:00
|
|
|
|
2019-11-01 03:05:40 -04:00
|
|
|
playerToEditPrompt :: Prompt
|
2019-11-01 03:44:03 -04:00
|
|
|
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
|
|
|
|
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
|
2019-11-01 03:05:40 -04:00
|
|
|
|
2019-08-24 21:15:50 -04:00
|
|
|
drawSimplePrompt :: String -> ProgState -> C.Update ()
|
2019-08-31 11:27:02 -04:00
|
|
|
drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer
|