mtlstats/src/Mtlstats/Actions.hs

232 lines
6.2 KiB
Haskell
Raw Normal View History

2019-08-20 11:17:24 -04:00
{- |
mtlstats
2023-05-23 17:22:14 -04:00
Copyright (C) Rhéal Lamothe
2019-08-20 11:17:24 -04:00
<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/>.
-}
2023-05-31 20:08:49 -04:00
{-# LANGUAGE ScopedTypeVariables #-}
2019-08-24 17:01:18 -04:00
2019-08-20 12:50:39 -04:00
module Mtlstats.Actions
( startNewSeason
, resetYtd
2020-01-11 02:29:17 -05:00
, clearRookies
2019-11-14 11:21:52 -05:00
, resetStandings
2019-08-20 12:50:39 -04:00
, startNewGame
, 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
, editSelectedPlayer
2019-11-12 23:44:39 -05:00
, editGoalie
, editSelectedGoalie
, addPlayer
2019-10-25 01:07:04 -04:00
, addGoalie
, resetCreatePlayerState
, resetCreateGoalieState
2019-10-11 23:13:00 -04:00
, backHome
2023-05-31 20:08:49 -04:00
, clearEditor
2020-03-12 02:44:41 -04:00
, loadDatabase
, saveDatabase
2019-08-20 12:50:39 -04:00
) where
2019-08-20 11:17:24 -04:00
2023-05-25 19:36:03 -04:00
import Brick.Main (viewportScroll)
2023-05-31 20:08:49 -04:00
import Brick.Widgets.Edit (Editor, applyEdit)
2020-03-12 02:44:41 -04:00
import Control.Exception (IOException, catch)
import Control.Monad.IO.Class (liftIO)
2023-05-25 19:36:03 -04:00
import Control.Monad.State.Class (modify)
2020-03-12 02:44:41 -04:00
import Data.Aeson (decodeFileStrict, encodeFile)
import Data.Maybe (fromMaybe)
2023-05-31 20:08:49 -04:00
import Data.Text.Zipper (gotoBOF, killToEOF)
import Lens.Micro ((^.), (&), (.~), (%~))
2023-05-25 19:36:03 -04:00
import Lens.Micro.Mtl ((.=), use)
import System.EasyFile
( createDirectoryIfMissing
, getAppUserDataDirectory
, (</>)
)
2019-08-20 12:26:24 -04:00
import Mtlstats.Config
2019-08-20 11:17:24 -04:00
import Mtlstats.Types
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
startNewSeason
= (progMode .~ NewSeason False)
. (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
2020-01-11 02:29:17 -05:00
-- | Clears the rookie flag from all players/goalies
clearRookies :: ProgState -> ProgState
clearRookies = database
%~ (dbPlayers %~ map (pRookie .~ False))
. (dbGoalies %~ map (gRookie .~ False))
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)
. (database . dbGames %~ succ)
2019-08-24 16:23:56 -04:00
-- | Starts player creation mode
createPlayer :: ProgState -> ProgState
2019-09-13 23:54:36 -04:00
createPlayer = let
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-10-25 00:37:14 -04:00
-- | Starts goalie creation mode
createGoalie :: ProgState -> ProgState
createGoalie = let
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
-- | Edits the selected 'Player'
editSelectedPlayer
:: (Player -> Player)
-- ^ The modification to be made to the 'Player'
-> ProgState
-> ProgState
editSelectedPlayer f s = fromMaybe s $ do
n <- s^.progMode.editPlayerStateL.epsSelectedPlayer
let
players = s^.database.dbPlayers
players' = modifyNth n f players
Just $ s & database.dbPlayers .~ players'
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
-- | Edits the selected 'Goalie'
editSelectedGoalie
:: (Goalie -> Goalie)
-- ^ The modification to be made to the 'Goalie'
-> ProgState
-> ProgState
editSelectedGoalie f s = fromMaybe s $ do
n <- s^.progMode.editGoalieStateL.egsSelectedGoalie
let
goalies = s^.database.dbGoalies
goalies' = modifyNth n f goalies
Just $ s & database.dbGoalies .~ goalies'
-- | Adds the entered player to the roster
addPlayer :: ProgState -> ProgState
addPlayer s = fromMaybe s $ do
let cps = s^.progMode.createPlayerStateL
2020-02-13 10:35:35 -05:00
num <- cps^.cpsNumber
rFlag <- cps^.cpsRookieFlag
2020-02-13 23:40:43 -05:00
aFlag <- cps^.cpsActiveFlag
let
name = cps^.cpsName
pos = cps^.cpsPosition
player = newPlayer num name pos
2020-02-13 10:35:35 -05:00
& pRookie .~ rFlag
2020-02-13 23:40:43 -05:00
& pActive .~ aFlag
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
2019-10-26 02:05:55 -04:00
addGoalie s = fromMaybe s $ do
let cgs = s^.progMode.createGoalieStateL
num <- cgs^.cgsNumber
rFlag <- cgs^.cgsRookieFlag
2020-02-13 23:55:00 -05:00
aFlag <- cgs^.cgsActiveFlag
2019-10-26 02:05:55 -04:00
let
name = cgs^.cgsName
goalie = newGoalie num name
& gRookie .~ rFlag
2020-02-13 23:55:00 -05:00
& gActive .~ aFlag
2019-10-26 02:05:55 -04:00
Just $ s & database.dbGoalies
%~ (++[goalie])
2019-10-25 01:07:04 -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
2023-05-31 20:08:49 -04:00
= (progMode .~ MainMenu)
. (editorW %~ clearEditor)
. (scroller .~ viewportScroll ())
-- | Clears an editor
clearEditor :: Editor String () -> Editor String ()
clearEditor = applyEdit $ killToEOF . gotoBOF
2020-03-12 02:44:41 -04:00
-- | Loads the database
loadDatabase :: Action ()
loadDatabase = do
dbFile <- dbSetup
liftIO
(catch
(decodeFileStrict dbFile)
(\(_ :: IOException) -> return Nothing))
2023-05-25 19:36:03 -04:00
>>= mapM_ (database .=)
2020-03-12 02:44:41 -04:00
-- | Saves the database
2020-03-12 02:44:41 -04:00
saveDatabase :: Action ()
saveDatabase = do
2023-05-25 19:36:03 -04:00
db <- use database
2020-03-12 02:44:41 -04:00
dbFile <- dbSetup
liftIO $ encodeFile dbFile db
dbSetup :: Action String
dbSetup = do
2023-05-25 19:36:03 -04:00
fn <- use dbName
liftIO $ do
dir <- getAppUserDataDirectory appName
createDirectoryIfMissing True dir
2020-03-12 02:44:41 -04:00
return $ dir </> fn ++ ".json"