mtlstats/src/Mtlstats/Actions.hs

264 lines
7.5 KiB
Haskell
Raw Normal View History

2019-08-20 11:17:24 -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-08-24 17:01:18 -04:00
{-# LANGUAGE LambdaCase #-}
2019-08-20 12:50:39 -04:00
module Mtlstats.Actions
( startNewSeason
, resetYtd
, startNewGame
2019-08-24 16:23:56 -04:00
, addChar
, removeChar
2019-08-29 00:12:30 -04:00
, overtimeCheck
2019-08-30 01:21:17 -04:00
, updateGameStats
2019-09-01 00:29:33 -04:00
, validateGameDate
, createPlayer
2019-10-25 00:37:14 -04:00
, createGoalie
, addPlayer
2019-10-25 01:07:04 -04:00
, addGoalie
2019-09-26 01:23:34 -04:00
, recordGoalAssists
2019-09-19 05:29:55 -04:00
, awardGoal
2019-09-26 02:07:55 -04:00
, awardAssist
2019-10-01 00:58:15 -04:00
, resetGoalData
2019-10-09 22:32:14 -04:00
, assignPMins
2019-10-11 23:13:00 -04:00
, backHome
2019-10-15 00:16:44 -04:00
, scrollUp
, scrollDown
2019-08-20 12:50:39 -04:00
) where
2019-08-20 11:17:24 -04:00
import Control.Monad.Trans.State (modify)
2019-10-03 02:10:22 -04:00
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
2019-09-01 00:29:33 -04:00
import Data.Time.Calendar (fromGregorianValid)
2019-08-30 01:21:17 -04:00
import Lens.Micro (over, (^.), (&), (.~), (?~), (%~), (+~))
2019-08-20 12:26:24 -04:00
2019-08-20 11:17:24 -04:00
import Mtlstats.Types
2019-10-11 01:10:50 -04:00
import Mtlstats.Util
2019-08-20 11:17:24 -04:00
2019-08-20 12:25:40 -04:00
-- | Starts a new season
2019-08-20 11:17:24 -04:00
startNewSeason :: ProgState -> ProgState
2019-08-20 12:26:24 -04:00
startNewSeason = (progMode .~ NewSeason) . (database . dbGames .~ 0)
2019-08-20 11:17:24 -04:00
2019-08-20 12:50:39 -04:00
-- | Resets all players year-to-date stats
resetYtd :: ProgState -> ProgState
2019-08-21 15:57:52 -04:00
resetYtd
= (database . dbPlayers %~ map (pYtd .~ newPlayerStats))
. (database . dbGoalies %~ map (gYtd .~ newGoalieStats))
2019-08-20 12:50:39 -04:00
2019-08-20 12:25:40 -04:00
-- | Starts a new game
2019-08-20 11:17:24 -04:00
startNewGame :: ProgState -> ProgState
2019-08-22 01:18:02 -04:00
startNewGame
= (progMode .~ NewGame newGameState)
. (database . dbGames %~ succ)
2019-08-24 16:23:56 -04:00
-- | Adds a character to the input buffer
addChar :: Char -> ProgState -> ProgState
2019-08-24 17:01:18 -04:00
addChar c = inputBuffer %~ (++[c])
2019-08-24 16:23:56 -04:00
-- | Removes a character from the input buffer (if possible)
removeChar :: ProgState -> ProgState
2019-08-24 17:01:18 -04:00
removeChar = inputBuffer %~ \case
"" -> ""
str -> init str
2019-08-29 00:12:30 -04:00
-- | Determines whether or not to perform a check for overtime
overtimeCheck :: ProgState -> ProgState
overtimeCheck s
| fromMaybe False $ gameTied $ s^.progMode.gameStateL =
2019-08-29 00:12:30 -04:00
s & progMode.gameStateL
%~ (homeScore .~ Nothing)
. (awayScore .~ Nothing)
| fromMaybe False $ gameWon $ s^.progMode.gameStateL =
2019-08-29 00:12:30 -04:00
s & progMode.gameStateL.overtimeFlag ?~ False
| otherwise = s
2019-08-30 01:21:17 -04:00
-- | Adjusts the game stats based on the results of the current game
updateGameStats :: ProgState -> ProgState
updateGameStats s = fromMaybe s $ do
let gs = s^.progMode.gameStateL
gType <- gs^.gameType
won <- gameWon gs
lost <- gameLost gs
ot <- gs^.overtimeFlag
tScore <- teamScore gs
oScore <- otherScore gs
let
hw = if gType == HomeGame && won then 1 else 0
hl = if gType == HomeGame && lost then 1 else 0
hot = if gType == HomeGame && ot then 1 else 0
hgf = if gType == HomeGame then tScore else 0
hga = if gType == HomeGame then oScore else 0
aw = if gType == AwayGame && won then 1 else 0
al = if gType == AwayGame && lost then 1 else 0
aot = if gType == AwayGame && ot then 1 else 0
agf = if gType == AwayGame then tScore else 0
aga = if gType == AwayGame then oScore else 0
Just $ s
& database.dbHomeGameStats
%~ (gmsWins +~ hw)
. (gmsLosses +~ hl)
. (gmsOvertime +~ hot)
. (gmsGoalsFor +~ hgf)
. (gmsGoalsAgainst +~ hga)
& database.dbAwayGameStats
%~ (gmsWins +~ aw)
. (gmsLosses +~ al)
. (gmsOvertime +~ aot)
. (gmsGoalsFor +~ agf)
. (gmsGoalsAgainst +~ aga)
2019-09-01 00:29:33 -04:00
-- | Validates the game date
validateGameDate :: ProgState -> ProgState
validateGameDate s = fromMaybe s $ do
y <- toInteger <$> s^.progMode.gameStateL.gameYear
m <- s^.progMode.gameStateL.gameMonth
d <- s^.progMode.gameStateL.gameDay
Just $ if null $ fromGregorianValid y m d
then s & progMode.gameStateL
%~ (gameYear .~ Nothing)
. (gameMonth .~ Nothing)
. (gameDay .~ Nothing)
else s
-- | Starts player creation mode
createPlayer :: ProgState -> ProgState
2019-09-13 23:54:36 -04:00
createPlayer = let
2019-10-25 00:37:14 -04:00
callback = modify $ progMode .~ MainMenu
cps = newCreatePlayerState
& cpsSuccessCallback .~ callback
& cpsFailureCallback .~ callback
2019-09-13 23:54:36 -04:00
in progMode .~ CreatePlayer cps
2019-10-25 00:37:14 -04:00
-- | Starts goalie creation mode
createGoalie :: ProgState -> ProgState
createGoalie = let
callback = modify $ progMode .~ MainMenu
cgs = newCreateGoalieState
& cgsSuccessCallback .~ callback
& cgsFailureCallback .~ callback
in progMode .~ CreateGoalie cgs
-- | Adds the entered player to the roster
addPlayer :: ProgState -> ProgState
addPlayer s = fromMaybe s $ do
let cps = s^.progMode.createPlayerStateL
num <- cps^.cpsNumber
let
name = cps^.cpsName
pos = cps^.cpsPosition
player = newPlayer num name pos
Just $ s & database.dbPlayers
%~ (++[player])
2019-09-19 05:29:55 -04:00
2019-10-25 01:07:04 -04:00
-- | Adds the entered goalie to the roster
addGoalie :: ProgState -> ProgState
addGoalie = undefined
2019-09-26 01:23:34 -04:00
-- | Awards the goal and assists to the players
recordGoalAssists :: ProgState -> ProgState
2019-09-27 01:39:50 -04:00
recordGoalAssists ps = fromMaybe ps $ do
let gs = ps^.progMode.gameStateL
goalId <- gs^.goalBy
let assistIds = gs^.assistsBy
2019-09-27 01:39:50 -04:00
Just $ ps
& awardGoal goalId
& (\s -> foldr awardAssist s assistIds)
& progMode.gameStateL
%~ (goalBy .~ Nothing)
. (assistsBy .~ [])
. (pointsAccounted %~ succ)
. (confirmGoalDataFlag .~ False)
2019-09-26 01:23:34 -04:00
2019-09-19 05:29:55 -04:00
-- | Awards a goal to a player
awardGoal
:: Int
-- ^ The player's index number
-> ProgState
-> ProgState
awardGoal n ps = ps
2019-10-03 02:10:22 -04:00
& progMode.gameStateL.gamePlayerStats %~
(\m -> let
stats = M.findWithDefault newPlayerStats n m
in M.insert n (stats & psGoals %~ succ) m)
& database.dbPlayers %~ map
(\(i, p) -> if i == n
then p
& pYtd.psGoals %~ succ
& pLifetime.psGoals %~ succ
else p) . zip [0..]
2019-09-26 02:07:55 -04:00
-- | Awards an assist to a player
awardAssist
:: Int
-- ^ The player's index number
-> ProgState
-> ProgState
awardAssist n ps = ps
2019-10-03 02:28:16 -04:00
& progMode.gameStateL.gamePlayerStats %~
(\m -> let
stats = M.findWithDefault newPlayerStats n m
in M.insert n (stats & psAssists %~ succ) m)
& database.dbPlayers %~ map
(\(i, p) -> if i == n
then p
& pYtd.psAssists %~ succ
& pLifetime.psAssists %~ succ
else p) . zip [0..]
2019-10-01 00:58:15 -04:00
-- | Resets the entered data for the current goal
resetGoalData :: ProgState -> ProgState
2019-10-02 01:47:47 -04:00
resetGoalData ps = ps & progMode.gameStateL
%~ (goalBy .~ Nothing)
. (assistsBy .~ [])
. (confirmGoalDataFlag .~ False)
2019-10-09 22:32:14 -04:00
-- | Adds penalty minutes to a player
assignPMins
:: Int
-- ^ The number of minutes to add
-> ProgState
-> ProgState
2019-10-11 01:10:50 -04:00
assignPMins mins s = fromMaybe s $ do
n <- s^.progMode.gameStateL.selectedPlayer
Just $ s
& database.dbPlayers %~ modifyNth n
(((pYtd.psPMin) +~ mins) . ((pLifetime.psPMin) +~ mins))
& progMode.gameStateL
%~ ( gamePlayerStats %~ updateMap n newPlayerStats
(psPMin +~ mins)
)
. (selectedPlayer .~ Nothing)
2019-10-11 23:13:00 -04:00
-- | Resets the program state back to the main menu
backHome :: ProgState -> ProgState
backHome
= (progMode .~ MainMenu)
. (inputBuffer .~ "")
. (scrollOffset .~ 0)
2019-10-15 00:16:44 -04:00
-- | Scrolls the display up
scrollUp :: ProgState -> ProgState
scrollUp = scrollOffset %~ max 0 . pred
-- | Scrolls the display down
scrollDown :: ProgState -> ProgState
scrollDown = scrollOffset %~ succ