Merge pull request #80 from mtlstats/season-select

Select season database on startup
This commit is contained in:
Jonathan Lamothe 2020-03-12 03:27:04 -04:00 committed by GitHub
commit 0eb46cacce
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
7 changed files with 71 additions and 48 deletions

View File

@ -1,5 +1,8 @@
# Changelog for mtlstats # Changelog for mtlstats
## current
- Ask for database to load on start-up
## 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)

View File

@ -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 ()

View File

@ -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"

View File

@ -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

View File

@ -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

View File

@ -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,
@ -168,24 +170,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 +232,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: " $

View File

@ -50,6 +50,7 @@ module Mtlstats.Types (
-- ** ProgState Lenses -- ** ProgState Lenses
database, database,
progMode, progMode,
dbName,
inputBuffer, inputBuffer,
scrollOffset, scrollOffset,
-- ** ProgMode Lenses -- ** ProgMode Lenses
@ -233,6 +234,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
@ -781,6 +784,7 @@ newProgState :: ProgState
newProgState = ProgState newProgState = ProgState
{ _database = newDatabase { _database = newDatabase
, _progMode = TitleScreen , _progMode = TitleScreen
, _dbName = ""
, _inputBuffer = "" , _inputBuffer = ""
, _scrollOffset = 0 , _scrollOffset = 0
} }