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
|
2019-11-14 11:21:52 -05:00
|
|
|
, resetStandings
|
2019-08-20 12:50:39 -04:00
|
|
|
, startNewGame
|
2019-08-24 16:23:56 -04:00
|
|
|
, addChar
|
|
|
|
, removeChar
|
2019-09-09 10:51:32 -04:00
|
|
|
, createPlayer
|
2019-10-25 00:37:14 -04:00
|
|
|
, createGoalie
|
2019-12-17 12:04:11 -05:00
|
|
|
, edit
|
2019-11-01 04:00:29 -04:00
|
|
|
, editPlayer
|
2019-11-12 23:44:39 -05:00
|
|
|
, editGoalie
|
2019-09-09 23:35:28 -04:00
|
|
|
, addPlayer
|
2019-10-25 01:07:04 -04:00
|
|
|
, addGoalie
|
2019-10-25 01:44:56 -04:00
|
|
|
, resetCreatePlayerState
|
|
|
|
, resetCreateGoalieState
|
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
|
|
|
|
2019-09-19 04:01:28 -04:00
|
|
|
import Control.Monad.Trans.State (modify)
|
2019-08-30 00:43:09 -04:00
|
|
|
import Data.Maybe (fromMaybe)
|
2019-11-07 23:37:46 -05:00
|
|
|
import Lens.Micro ((^.), (&), (.~), (%~))
|
2019-08-20 12:26:24 -04:00
|
|
|
|
2019-08-20 11:17:24 -04:00
|
|
|
import Mtlstats.Types
|
|
|
|
|
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-11-14 11:21:52 -05:00
|
|
|
-- | Resets game standings
|
|
|
|
resetStandings :: ProgState -> ProgState
|
|
|
|
resetStandings = database
|
|
|
|
%~ ( dbHomeGameStats .~ newGameStats)
|
|
|
|
. ( dbAwayGameStats .~ newGameStats)
|
|
|
|
|
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)
|
2019-08-23 09:32:21 -04:00
|
|
|
. (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
|
|
|
|
2019-09-09 10:51:32 -04:00
|
|
|
-- | Starts player creation mode
|
|
|
|
createPlayer :: ProgState -> ProgState
|
2019-09-13 23:54:36 -04:00
|
|
|
createPlayer = let
|
2019-12-17 12:30:55 -05:00
|
|
|
callback = modify edit
|
2019-10-25 00:37:14 -04:00
|
|
|
cps = newCreatePlayerState
|
|
|
|
& cpsSuccessCallback .~ callback
|
|
|
|
& cpsFailureCallback .~ callback
|
2019-09-13 23:54:36 -04:00
|
|
|
in progMode .~ CreatePlayer cps
|
2019-09-09 23:35:28 -04:00
|
|
|
|
2019-10-25 00:37:14 -04:00
|
|
|
-- | Starts goalie creation mode
|
|
|
|
createGoalie :: ProgState -> ProgState
|
|
|
|
createGoalie = let
|
2019-12-17 12:30:55 -05:00
|
|
|
callback = modify edit
|
2019-10-25 00:37:14 -04:00
|
|
|
cgs = newCreateGoalieState
|
|
|
|
& cgsSuccessCallback .~ callback
|
|
|
|
& cgsFailureCallback .~ callback
|
|
|
|
in progMode .~ CreateGoalie cgs
|
|
|
|
|
2019-12-17 12:04:11 -05:00
|
|
|
-- | Launches the edit menu
|
|
|
|
edit :: ProgState -> ProgState
|
2019-12-17 12:16:26 -05:00
|
|
|
edit = progMode .~ EditMenu
|
2019-12-17 12:04:11 -05:00
|
|
|
|
2019-11-01 04:00:29 -04:00
|
|
|
-- | Starts the player editing process
|
|
|
|
editPlayer :: ProgState -> ProgState
|
|
|
|
editPlayer = progMode .~ EditPlayer newEditPlayerState
|
|
|
|
|
2019-11-12 23:44:39 -05:00
|
|
|
-- | Starts the 'Goalie' editing process
|
|
|
|
editGoalie :: ProgState -> ProgState
|
2019-11-12 23:48:31 -05:00
|
|
|
editGoalie = progMode .~ EditGoalie newEditGoalieState
|
2019-11-12 23:44:39 -05:00
|
|
|
|
2019-09-09 23:35:28 -04:00
|
|
|
-- | 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
|
2019-09-28 01:46:28 -04:00
|
|
|
%~ (++[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
|
2019-10-26 02:05:55 -04:00
|
|
|
addGoalie s = fromMaybe s $ do
|
|
|
|
let cgs = s^.progMode.createGoalieStateL
|
|
|
|
num <- cgs^.cgsNumber
|
|
|
|
let
|
|
|
|
name = cgs^.cgsName
|
|
|
|
goalie = newGoalie num name
|
|
|
|
Just $ s & database.dbGoalies
|
|
|
|
%~ (++[goalie])
|
2019-10-25 01:07:04 -04:00
|
|
|
|
2019-10-25 01:44:56 -04:00
|
|
|
-- | Resets the 'CreatePlayerState' value
|
|
|
|
resetCreatePlayerState :: ProgState -> ProgState
|
|
|
|
resetCreatePlayerState = progMode.createPlayerStateL
|
|
|
|
%~ (cpsNumber .~ Nothing)
|
|
|
|
. (cpsName .~ "")
|
|
|
|
. (cpsPosition .~ "")
|
|
|
|
|
|
|
|
-- | Resets the 'CreateGoalieState' value
|
|
|
|
resetCreateGoalieState :: ProgState -> ProgState
|
|
|
|
resetCreateGoalieState = progMode.createGoalieStateL
|
|
|
|
%~ (cgsNumber .~ Nothing)
|
|
|
|
. (cgsName .~ "")
|
|
|
|
|
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
|