mtlstats/src/Mtlstats/Menu.hs

167 lines
4.5 KiB
Haskell

{- |
mtlstats
Copyright (C) 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/>.
-}
module Mtlstats.Menu (
-- * Menu Functions
menuController,
menuControllerWith,
menuStateController,
drawMenu,
menuHandler,
-- * Menus
mainMenu,
newSeasonMenu,
gameTypeMenu,
gameGoalieMenu,
editMenu
) where
import Brick.Main (halt)
import Brick.Types (BrickEvent (VtyEvent), Widget)
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Core (str, vBox)
import Control.Monad.State.Class (gets, modify)
import Data.Char (toUpper)
import qualified Data.Map as M
import Data.Maybe (mapMaybe)
import Graphics.Vty.Input.Events (Event (EvKey), Key (KChar))
import Lens.Micro ((^.), (?~))
import Mtlstats.Actions
import qualified Mtlstats.Actions.NewGame.GoalieInput as GI
import Mtlstats.Actions.EditStandings
import Mtlstats.Types
import Mtlstats.Types.Menu
import Mtlstats.Util
-- | Generates a simple 'Controller' for a Menu
menuController :: Menu () -> Controller
menuController = menuControllerWith $ const id
-- | Generate a simple 'Controller' for a 'Menu' with a header
menuControllerWith
:: (ProgState -> Widget () -> Widget())
-- ^ Function to attach the header
-> Menu ()
-- ^ The menu
-> Controller
-- ^ The resulting controller
menuControllerWith header menu = Controller
{ drawController = \s -> header s $ drawMenu menu
, handleController = menuHandler menu
}
-- | Generate and create a controller for a menu based on the current
-- 'ProgState'
menuStateController
:: (ProgState -> Menu ())
-- ^ The function to generate the menu
-> Controller
-- ^ The resulting controller
menuStateController menuFunc = Controller
{ drawController = drawMenu . menuFunc
, handleController = \e -> do
menu <- gets menuFunc
menuHandler menu e
}
-- | The draw function for a 'Menu'
drawMenu :: Menu a -> Widget ()
drawMenu m = let
menuLines = lines $ show m
in hCenter $ vBox $ map str menuLines
-- | The event handler for a 'Menu'
menuHandler :: Menu a -> Handler a
menuHandler m (VtyEvent (EvKey (KChar c) [])) =
case filter (\i -> i^.miKey == toUpper c) $ m^.menuItems of
i:_ -> i^.miAction
[] -> return $ m^.menuDefault
menuHandler m _ = return $ m^.menuDefault
-- | The main menu
mainMenu :: Menu ()
mainMenu = Menu "MASTER MENU" ()
[ MenuItem 'A' "NEW SEASON" $
modify startNewSeason
, MenuItem 'B' "NEW GAME" $
modify startNewGame
, MenuItem 'C' "EDIT MENU" $
modify edit
, MenuItem 'E' "EXIT" $
saveDatabase >> halt
]
-- | The new season menu
newSeasonMenu :: Menu ()
newSeasonMenu = Menu "SEASON TYPE" ()
[ MenuItem 'R' "REGULAR SEASON" $ modify
$ resetYtd
. clearRookies
. resetStandings
. backHome
, MenuItem 'P' "PLAYOFFS" $ modify
$ resetStandings
. backHome
]
-- | The game type menu (home/away)
gameTypeMenu :: Menu ()
gameTypeMenu = Menu "GAME TYPE:" ()
[ MenuItem 'H' "HOME GAME" $
modify $ progMode.gameStateL.gameType ?~ HomeGame
, MenuItem 'A' "AWAY GAME" $
modify $ progMode.gameStateL.gameType ?~ AwayGame
]
-- | Game goalie selection menu
gameGoalieMenu :: ProgState -> Menu ()
gameGoalieMenu s = let
title = "Which goalie should get credit for the game?"
gids = map fst $ M.toList $ s^.progMode.gameStateL.gameGoalieStats
goalies = mapMaybe
(\n -> do
goalie <- nth n $ s^.database.dbGoalies
Just (n, goalie))
gids
in Menu title () $ zipWith
(\ch (gid, goalie) -> MenuItem ch (goalieSummary goalie) $
modify $ GI.setGameGoalie gid)
['1'..]
goalies
-- | The edit menu
editMenu :: Menu ()
editMenu = Menu "EDIT MENU" ()
[ MenuItem 'A' "CREATE PLAYER" $
modify createPlayer
, MenuItem 'B' "CREATE GOALIE" $
modify createGoalie
, MenuItem 'C' "EDIT PLAYER" $
modify editPlayer
, MenuItem 'D' "EDIT GOALIE" $
modify editGoalie
, MenuItem 'E' "EDIT STANDINGS" $
modify editStandings
, MenuItem 'R' "RETURN TO MAIN MENU" $
modify backHome
]