21 Commits

Author SHA1 Message Date
93048d6053 version 0.17.0.1 2023-06-04 18:04:41 -04:00
d55f7b1f50 force capitalization in ucStrPrompt 2023-06-04 17:53:48 -04:00
a5679cb1fc version 0.17.0 2023-06-02 15:30:44 -04:00
bdbf7daf4e Merge pull request 'switch from ncurses to brick' (#1) from brick into dev
Reviewed-on: #1
2023-06-02 15:28:41 -04:00
e0efe2657f ynHandler should ignore keypresses with modifier keys 2023-06-02 15:26:22 -04:00
886cf0b243 even more stylistic changes
I hope to God I'm done with these now.
2023-06-01 19:51:04 -04:00
251dc90cea more stylistic changes 2023-06-01 19:06:46 -04:00
17b3f9a03e minor stylistic edits 2023-06-01 18:39:46 -04:00
01457dbe6f removed signature line 2023-06-01 17:18:09 -04:00
134787e1be removed Travis CI configuration file 2023-06-01 17:15:29 -04:00
284a8c6725 various layout fixes 2023-05-31 22:19:18 -04:00
d92722be9c use Editor istead of String 2023-05-31 20:08:49 -04:00
820aab5e96 fix layout of selection prompt 2023-05-31 13:21:49 -04:00
2d5c4e6471 fixed spacing on title screen 2023-05-30 19:01:30 -04:00
097d51f34b properly centre menu headings 2023-05-30 18:56:44 -04:00
166483dc50 fixed missing blank line between menu header and options 2023-05-30 18:45:03 -04:00
08e0f96a81 cursor position fix
cursor X and Y coordinates were transposed for the simple string prompts
2023-05-30 18:30:49 -04:00
afae5ea14a updated ChangeLog 2023-05-30 18:21:56 -04:00
ea9a9c6a85 bugfix: backspace
backspace functionality was mistakenly mapped to the escape key for some reason
2023-05-30 18:11:54 -04:00
d40b56da37 bail on CTRL-C 2023-05-30 18:06:32 -04:00
5ea2d77921 bugfix: make the whole background blue 2023-05-30 17:58:45 -04:00
20 changed files with 186 additions and 170 deletions

View File

@@ -1,40 +0,0 @@
# This is the simple Travis configuration, which is intended for use
# on applications which do not require cross-platform and
# multiple-GHC-version support. For more information and other
# options, see:
#
# https://docs.haskellstack.org/en/stable/travis_ci/
#
# Copy these contents into the root directory of your Github project in a file
# named .travis.yml
# Choose a build environment
dist: xenial
# Do not choose a language; we provide our own build tools.
language: generic
# Caching so the next build will be fast too.
cache:
directories:
- $HOME/.stack
# Ensure necessary system libraries are present
addons:
apt:
packages:
- libgmp-dev
before_install:
# Download and unpack the stack executable
- mkdir -p ~/.local/bin
- export PATH=$HOME/.local/bin:$PATH
- travis_retry curl -L https://get.haskellstack.org/stable/linux-x86_64.tar.gz | tar xz --wildcards --strip-components=1 -C ~/.local/bin '*/stack'
install:
# Build dependencies
- stack --no-terminal --install-ghc test --only-dependencies
script:
# Build the package, its tests, and its docs and run the tests
- stack --no-terminal test --haddock --no-haddock-deps

View File

@@ -1,5 +1,11 @@
# Changelog for mtlstats
## 0.17.0.1
- fixed autocapitalization
## 0.17.0
- updated code to use brick instead of ncurses
## 0.16.1
- Don't automatically start a new game on new season

View File

@@ -1,5 +1,5 @@
name: mtlstats
version: 0.16.1
version: 0.17.0.1
license: GPL-3.0-or-later
author: "Jonathan Lamothe"
maintainer: "jlamothe1980@gmail.com"
@@ -31,6 +31,7 @@ dependencies:
- microlens-th >= 0.4.2.3 && < 0.5
- mtl >= 2.2.2 && < 2.3
- random >= 1.2.1.1 && < 1.3
- text-zipper >= 0.12 && < 0.13
- time >= 1.11.1.1 && < 1.12
- vty >= 5.37 && < 5.38

View File

@@ -22,11 +22,17 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats (app) where
import Brick.AttrMap (AttrMap, forceAttrMap)
import Brick.Main (App (..), showFirstCursor)
import Brick.Main (App (..), halt, showFirstCursor)
import Brick.Types (BrickEvent (VtyEvent), Widget)
import Brick.Util (on)
import Brick.Widgets.Core (fill)
import Control.Monad.State.Class (gets)
import Graphics.Vty.Attributes.Color (blue, white)
import Lens.Micro (to)
import Lens.Micro.Mtl (use)
import Graphics.Vty.Input.Events
( Event (EvKey)
, Modifier (MCtrl)
, Key (KChar)
)
import Mtlstats.Control
import Mtlstats.Types
@@ -34,19 +40,24 @@ import Mtlstats.Types
-- | The main application
app :: App ProgState () ()
app = App
{ appDraw = \s -> [drawController (dispatch s) s]
{ appDraw = draw
, appChooseCursor = showFirstCursor
, appHandleEvent = handler
, appStartEvent = return ()
, appAttrMap = const myAttrMap
}
draw :: ProgState -> [Widget ()]
draw s =
[ drawController (dispatch s) s
, fill ' '
]
handler :: Handler ()
handler (VtyEvent (EvKey (KChar 'c') [MCtrl])) = halt
handler e = do
c <- use (to dispatch)
c <- gets dispatch
handleController c e
myAttrMap :: AttrMap
myAttrMap = forceAttrMap (white `on` blue)
--jl

View File

@@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE LambdaCase, ScopedTypeVariables #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Mtlstats.Actions
( startNewSeason
@@ -27,8 +27,6 @@ module Mtlstats.Actions
, clearRookies
, resetStandings
, startNewGame
, addChar
, removeChar
, createPlayer
, createGoalie
, edit
@@ -41,16 +39,19 @@ module Mtlstats.Actions
, resetCreatePlayerState
, resetCreateGoalieState
, backHome
, clearEditor
, loadDatabase
, saveDatabase
) where
import Brick.Main (viewportScroll)
import Brick.Widgets.Edit (Editor, applyEdit)
import Control.Exception (IOException, catch)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.State.Class (modify)
import Data.Aeson (decodeFileStrict, encodeFile)
import Data.Maybe (fromMaybe)
import Data.Text.Zipper (gotoBOF, killToEOF)
import Lens.Micro ((^.), (&), (.~), (%~))
import Lens.Micro.Mtl ((.=), use)
import System.EasyFile
@@ -93,16 +94,6 @@ startNewGame
= (progMode .~ NewGame newGameState)
. (database . dbGames %~ succ)
-- | Adds a character to the input buffer
addChar :: Char -> ProgState -> ProgState
addChar c = inputBuffer %~ (++[c])
-- | Removes a character from the input buffer (if possible)
removeChar :: ProgState -> ProgState
removeChar = inputBuffer %~ \case
"" -> ""
str -> init str
-- | Starts player creation mode
createPlayer :: ProgState -> ProgState
createPlayer = let
@@ -206,9 +197,13 @@ resetCreateGoalieState = progMode.createGoalieStateL
-- | Resets the program state back to the main menu
backHome :: ProgState -> ProgState
backHome
= (progMode .~ MainMenu)
. (inputBuffer .~ "")
. (scroller .~ viewportScroll ())
= (progMode .~ MainMenu)
. (editorW %~ clearEditor)
. (scroller .~ viewportScroll ())
-- | Clears an editor
clearEditor :: Editor String () -> Editor String ()
clearEditor = applyEdit $ killToEOF . gotoBOF
-- | Loads the database
loadDatabase :: Action ()

View File

@@ -24,6 +24,7 @@ module Mtlstats.Control.CreateGoalie (createGoalieC) where
import Brick.Widgets.Core (str)
import Control.Monad.State.Class (gets, modify)
import Lens.Micro ((^.), (.~), (?~), (%~), to)
import Lens.Micro.Mtl ((.=))
import Mtlstats.Actions
import Mtlstats.Format
@@ -63,7 +64,7 @@ getActiveFlagC :: Controller
getActiveFlagC = Controller
{ drawController = const $ str "Is this goalie active? (Y/N)"
, handleController = \e ->
modify $ progMode.createGoalieStateL.cgsActiveFlag .~ ynHandler e
progMode.createGoalieStateL.cgsActiveFlag .= ynHandler e
}
confirmCreateGoalieC :: Controller

View File

@@ -24,6 +24,7 @@ module Mtlstats.Control.CreatePlayer (createPlayerC) where
import Brick.Widgets.Core (str)
import Control.Monad.State.Class (gets, modify)
import Lens.Micro ((^.), (.~), (?~), (%~), to)
import Lens.Micro.Mtl ((.=), use)
import Mtlstats.Actions
import Mtlstats.Format
@@ -66,7 +67,7 @@ getActiveFlagC :: Controller
getActiveFlagC = Controller
{ drawController = const $ str "Is the player active? (Y/N)"
, handleController = \e ->
modify $ progMode.createPlayerStateL.cpsActiveFlag .~ ynHandler e
progMode.createPlayerStateL.cpsActiveFlag .= ynHandler e
}
confirmCreatePlayerC :: Controller
@@ -84,7 +85,7 @@ confirmCreatePlayerC = Controller
, "Create player: are you sure? (Y/N)"
]
, handleController = \e -> do
cps <- gets (^.progMode.createPlayerStateL)
cps <- use $ progMode.createPlayerStateL
let
success = cps^.cpsSuccessCallback
failure = cps^.cpsFailureCallback

View File

@@ -25,9 +25,10 @@ module Mtlstats.Control.EditGoalie (editGoalieC) where
import Brick.Types (Widget)
import Brick.Widgets.Core (str, vBox)
import Control.Monad.State.Class (gets, modify)
import Control.Monad.State.Class (modify)
import Data.Maybe (fromMaybe)
import Lens.Micro ((^.), (.~), (%~))
import Lens.Micro ((^.))
import Lens.Micro.Mtl ((.=), (%=), use)
import Mtlstats.Actions
import Mtlstats.Handlers
@@ -99,10 +100,10 @@ deleteC _ = Controller
in str $ hdr ++ "Are you sure you want to delete this goalie? (Y/N)"
, handleController = \e -> case ynHandler e of
Just True -> do
gets (^.progMode.editGoalieStateL.egsSelectedGoalie) >>= mapM_
(\gid -> modify $ database.dbGoalies %~ dropNth gid)
use (progMode.editGoalieStateL.egsSelectedGoalie) >>= mapM_
(\gid -> database.dbGoalies %= dropNth gid)
modify edit
Just False -> modify $ progMode.editGoalieStateL.egsMode .~ EGMenu
Just False -> progMode.editGoalieStateL.egsMode .= EGMenu
Nothing -> return ()
}

View File

@@ -23,9 +23,10 @@ module Mtlstats.Control.EditPlayer (editPlayerC) where
import Brick.Types (Widget)
import Brick.Widgets.Core (emptyWidget, str, vBox)
import Control.Monad.State.Class (gets, modify)
import Control.Monad.State.Class (modify)
import Data.Maybe (fromMaybe)
import Lens.Micro ((^.), (.~), (%~))
import Lens.Micro ((^.))
import Lens.Micro.Mtl ((.=), (%=), use)
import Mtlstats.Actions
import Mtlstats.Handlers
@@ -90,10 +91,10 @@ deleteC _ = Controller
in str $ hdr ++ "Are you sure you want to delete this player? (Y/N)"
, handleController = \e -> case ynHandler e of
Just True -> do
gets (^.progMode.editPlayerStateL.epsSelectedPlayer) >>= mapM_
(\pid -> modify $ database.dbPlayers %~ dropNth pid)
use (progMode.editPlayerStateL.epsSelectedPlayer) >>= mapM_
(\pid -> database.dbPlayers %= dropNth pid)
modify edit
Just False -> modify $ progMode.editPlayerStateL.epsMode .~ EPMenu
Just False -> progMode.editPlayerStateL.epsMode .= EPMenu
Nothing -> return ()
}

View File

@@ -24,7 +24,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Control.EditStandings (editStandingsC) where
import Brick.Types (Widget)
import Brick.Widgets.Core (str, vBox)
import Brick.Widgets.Core (vBox)
import Lens.Micro ((^.))
import Mtlstats.Format
@@ -34,6 +34,7 @@ import Mtlstats.Prompt
import Mtlstats.Prompt.EditStandings
import Mtlstats.Types
import Mtlstats.Types.Menu
import Mtlstats.Util
-- | Controller for the edit standings menu
editStandingsC :: EditStandingsMode -> Controller
@@ -75,7 +76,10 @@ header s w = let
[ ( "HOME", valsFor home )
, ( "ROAD", valsFor away )
]
in vBox $ map str (table ++ [""]) ++ [w]
in vBox
[ linesToWidget $ table ++ [""]
, w
]
valsFor :: GameStats -> [Int]
valsFor gs =

View File

@@ -37,7 +37,7 @@ import Graphics.Vty.Input.Events
, Key (KDown, KHome, KEnter, KUp)
)
import Lens.Micro ((^.), (.~))
import Lens.Micro.Mtl (use)
import Lens.Micro.Mtl ((.=), use)
import Mtlstats.Actions
import Mtlstats.Actions.NewGame
@@ -96,14 +96,14 @@ overtimeFlagC = Controller
{ drawController = \s -> header s $
str "Did the game go into overtime? (Y/N)"
, handleController = \e ->
modify $ progMode.gameStateL.overtimeFlag .~ ynHandler e
progMode.gameStateL.overtimeFlag .= ynHandler e
}
verifyDataC :: Controller
verifyDataC = Controller
{ drawController = \s -> let
gs = s^.progMode.gameStateL
in header s $ vBox $ map str $
in header s $ linesToWidget $
[""] ++
labelTable
[ ( "Date", gameDate gs )
@@ -172,7 +172,7 @@ confirmGoalDataC = Controller
[ ""
, "Is the above information correct? (Y/N)"
]
in vBox $ map str msg
in linesToWidget msg
, handleController = \e -> do
case ynHandler e of
Just True -> modify recordGoalAssists
@@ -201,7 +201,7 @@ getPMinsC = Controller
reportC :: Controller
reportC = Controller
{ drawController = viewport () Vertical . hCenter . vBox . map str .
{ drawController = viewport () Vertical . hCenter . linesToWidget .
displayReport reportCols
, handleController = \e -> do
scr <- use scroller
@@ -239,8 +239,11 @@ monthHeader s w = let
, "NOVEMBER"
, "DECEMBER"
]
in header s $ vBox $ map (hCenter . str)
(["MONTH:", ""] ++ table ++ [""]) ++ [w]
in header s $ vBox
[ linesToWidgetC $
["MONTH:", ""] ++ table ++ [""]
, w
]
gameGoal :: ProgState -> (Int, Int)
gameGoal s =

View File

@@ -24,18 +24,17 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Mtlstats.Control.TitleScreen (titleScreenC) where
import Brick.Types (BrickEvent (VtyEvent))
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Core (str, vBox)
import Control.Monad.State.Class (modify)
import Data.Char (chr)
import Graphics.Vty.Input.Events (Event (EvKey))
import Mtlstats.Actions
import Mtlstats.Types
import Mtlstats.Util
titleScreenC :: Controller
titleScreenC = Controller
{ drawController = const $ vBox $ map (hCenter . str)
{ drawController = const $ linesToWidgetC
$ [ ""
, "MONTREAL CANADIENS STATISTICS"
]
@@ -48,7 +47,7 @@ titleScreenC = Controller
]
, handleController = \case
VtyEvent (EvKey _ _) -> modify backHome
_ -> return ()
_ -> return ()
}
titleText :: [String]

View File

@@ -27,7 +27,7 @@ import Graphics.Vty.Input.Events (Event (EvKey), Key (KChar))
-- | Handler for a yes/no prompt
ynHandler :: BrickEvent () () -> Maybe Bool
ynHandler (VtyEvent (EvKey (KChar c) _)) = case toUpper c of
ynHandler (VtyEvent (EvKey (KChar c) [])) = case toUpper c of
'Y' -> Just True
'N' -> Just False
_ -> Nothing

View File

@@ -36,8 +36,6 @@ module Mtlstats.Menu (
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
@@ -87,7 +85,7 @@ menuStateController menuFunc = Controller
drawMenu :: Menu a -> Widget ()
drawMenu m = let
menuLines = lines $ show m
in hCenter $ vBox $ map str menuLines
in linesToWidgetC menuLines
-- | The event handler for a 'Menu'
menuHandler :: Menu a -> Handler a

View File

@@ -48,19 +48,20 @@ module Mtlstats.Prompt (
playerToEditPrompt
) where
import Brick.Types (BrickEvent (VtyEvent), Location (Location), Widget)
import Brick.Widgets.Core (hBox, showCursor, str)
import Brick.Types (BrickEvent (VtyEvent), Widget)
import Brick.Widgets.Core (hBox, str, vBox)
import Brick.Widgets.Edit (editContentsL, renderEditor)
import Control.Monad (when)
import Control.Monad.Extra (whenJust)
import Control.Monad.State.Class (gets, modify)
import Data.Char (isAlphaNum, isDigit, toUpper)
import Graphics.Text.Width (safeWcswidth)
import Data.Text.Zipper (deletePrevChar, insertChar)
import Graphics.Vty.Input.Events
( Event (EvKey)
, Key (KChar, KEnter, KEsc, KFun)
, Key (KBS, KChar, KEnter, KFun)
)
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import Lens.Micro.Mtl ((.=), use)
import Lens.Micro ((^.), (&), (.~), (?~), (%~), to)
import Lens.Micro.Mtl ((%=), use)
import Text.Read (readMaybe)
import Mtlstats.Actions
@@ -72,13 +73,13 @@ import Mtlstats.Util
-- | Event handler for a prompt
promptHandler :: Prompt -> Handler ()
promptHandler p (VtyEvent (EvKey KEnter [])) = do
val <- use inputBuffer
inputBuffer .= ""
val <- use $ editorW.to userText
editorW %= clearEditor
promptAction p val
promptHandler p (VtyEvent (EvKey (KChar c) [])) =
modify $ inputBuffer %~ promptProcessChar p c
promptHandler _ (VtyEvent (EvKey KEsc [])) =
modify removeChar
editorW %= promptProcessChar p c
promptHandler _ (VtyEvent (EvKey KBS [])) =
editorW.editContentsL %= deletePrevChar
promptHandler p (VtyEvent (EvKey k m)) =
promptSpecialKey p k m
promptHandler _ _ = return ()
@@ -113,7 +114,7 @@ strPrompt
-> Prompt
strPrompt pStr act = Prompt
{ drawPrompt = drawSimplePrompt pStr
, promptProcessChar = \ch -> (++ [ch])
, promptProcessChar = \ch -> editContentsL %~ insertChar ch
, promptAction = act
, promptSpecialKey = \_ _ -> return ()
}
@@ -126,7 +127,7 @@ ucStrPrompt
-- ^ The callback function for the result
-> Prompt
ucStrPrompt pStr act = (strPrompt pStr act)
{ promptProcessChar = \ch -> (++ [toUpper ch]) }
{ promptProcessChar = \ch -> editContentsL %~ insertChar (toUpper ch) }
-- | Creates a prompt which forces capitalization of input to
-- accomodate a player or goalie name
@@ -174,7 +175,7 @@ numPromptWithFallback
numPromptWithFallback pStr fallback act = Prompt
{ drawPrompt = drawSimplePrompt pStr
, promptProcessChar = \ch existing -> if isDigit ch
then existing ++ [ch]
then existing & editContentsL %~ insertChar ch
else existing
, promptAction = maybe fallback act . readMaybe
, promptSpecialKey = \_ _ -> return ()
@@ -189,7 +190,7 @@ dbNamePrompt
-> Prompt
dbNamePrompt pStr act = (strPrompt pStr act)
{ promptProcessChar = \ch -> if isAlphaNum ch || ch == '-'
then (++[toUpper ch])
then editContentsL %~ insertChar (toUpper ch)
else id
}
@@ -209,18 +210,20 @@ newSeasonPrompt = dbNamePrompt "Filename for new season: " $ \fn ->
selectPrompt :: SelectParams a -> Prompt
selectPrompt params = Prompt
{ drawPrompt = \s -> let
sStr = s^.inputBuffer
pStr = spPrompt params ++ sStr
pWidth = safeWcswidth pStr
sStr = s^.editorW.to userText
pStr = spPrompt params
results = zip [1..maxFunKeys] $ spSearch params sStr (s^.database)
fmtRes = map
(\(n, (_, x)) -> let
desc = spElemDesc params x
in str $ "F" ++ show n ++ ") " ++ desc)
results
in hBox $
[ showCursor () (Location (0, pWidth)) $ str pStr
, str ""
in vBox $
[ hBox
[ str pStr
, renderEditor linesToWidget True (s^.editorW)
]
, str " "
, str $ spSearchHeader params
] ++ fmtRes
, promptProcessChar = spProcessChar params
@@ -233,14 +236,14 @@ selectPrompt params = Prompt
Just n -> spCallback params $ Just n
, promptSpecialKey = \key _ -> case key of
KFun rawK -> do
sStr <- use inputBuffer
sStr <- use $ editorW . to userText
db <- use database
let
n = pred rawK
results = spSearch params sStr db
when (n < maxFunKeys) $
whenJust (nth n results) $ \(sel, _) -> do
modify $ inputBuffer .~ ""
editorW %= clearEditor
spCallback params $ Just sel
_ -> return ()
}
@@ -393,7 +396,7 @@ selectPositionPrompt pStr callback = selectPrompt SelectParams
, spSearch = posSearch
, spSearchExact = posSearchExact
, spElemDesc = id
, spProcessChar = \ch -> (++ [toUpper ch])
, spProcessChar = \c -> editContentsL %~ insertChar (toUpper c)
, spCallback = posCallback callback
, spNotFound = callback
}
@@ -403,7 +406,7 @@ playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
drawSimplePrompt :: String -> Renderer
drawSimplePrompt pStr s = let
fullStr = pStr ++ s^.inputBuffer
strWidth = safeWcswidth fullStr
in showCursor () (Location (0, strWidth)) $ str fullStr
drawSimplePrompt pStr s = hBox
[ str pStr
, renderEditor linesToWidget True (s^.editorW)
]

View File

@@ -53,7 +53,7 @@ module Mtlstats.Types (
database,
progMode,
dbName,
inputBuffer,
editorW,
scroller,
-- ** ProgMode Lenses
gameStateL,
@@ -199,6 +199,7 @@ module Mtlstats.Types (
import Brick.Main (ViewportScroll, viewportScroll)
import Brick.Types (BrickEvent, EventM, Widget)
import Brick.Widgets.Edit (Editor, editor)
import Data.Aeson
( FromJSON
, ToJSON
@@ -241,15 +242,15 @@ type Handler a = BrickEvent () () -> Action a
-- | Represents the program state
data ProgState = ProgState
{ _database :: Database
{ _database :: Database
-- ^ The data to be saved
, _progMode :: ProgMode
, _progMode :: ProgMode
-- ^ The program's mode
, _dbName :: String
, _dbName :: String
-- ^ The name of the database file
, _inputBuffer :: String
-- ^ Buffer for user input
, _scroller :: ViewportScroll ()
, _editorW :: Editor String ()
-- ^ Editor widget
, _scroller :: ViewportScroll ()
-- ^ Scroller for the reports
}
@@ -543,8 +544,8 @@ data GameStats = GameStats
data Prompt = Prompt
{ drawPrompt :: ProgState -> Widget ()
-- ^ Draws the prompt to the screen
, promptProcessChar :: Char -> String -> String
-- ^ Modifies the string based on the character entered
, promptProcessChar :: Char -> Editor String () -> Editor String ()
-- ^ Modifies an editor based on the character entered
, promptAction :: String -> Action ()
-- ^ Action to perform when the value is entered
, promptSpecialKey :: Key -> [Modifier] -> Action ()
@@ -563,7 +564,7 @@ data SelectParams a = SelectParams
-- ^ Search function looking for an exact match
, spElemDesc :: a -> String
-- ^ Provides a string description of an element
, spProcessChar :: Char -> String -> String
, spProcessChar :: Char -> Editor String () -> Editor String ()
-- ^ Processes a character entered by the user
, spCallback :: Maybe Int -> Action ()
-- ^ The function when the selection is made
@@ -795,11 +796,11 @@ esmSubModeL = lens
-- | Constructor for a 'ProgState'
newProgState :: ProgState
newProgState = ProgState
{ _database = newDatabase
, _progMode = TitleScreen
, _dbName = ""
, _inputBuffer = ""
, _scroller = viewportScroll ()
{ _database = newDatabase
, _progMode = TitleScreen
, _dbName = ""
, _editorW = editor () (Just 1) ""
, _scroller = viewportScroll ()
}
-- | Constructor for a 'GameState'

View File

@@ -27,12 +27,18 @@ module Mtlstats.Util
, slice
, capitalizeName
, linesToWidget
, linesToWidgetC
, userText
) where
import Brick.Types (Widget)
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Core (str, vBox)
import Brick.Widgets.Edit (Editor, editContentsL, getEditContents)
import Data.Char (isSpace, toUpper)
import qualified Data.Map as M
import Data.Text.Zipper (insertChar)
import Lens.Micro ((^.), (&), (%~), to)
-- | Attempt to select the element from a list at a given index
nth
@@ -104,12 +110,13 @@ slice offset len = take len . drop offset
capitalizeName
:: Char
-- ^ The character being input
-> String
-> Editor String ()
-- ^ The current string
-> String
-> Editor String ()
-- ^ The resulting string
capitalizeName ch s = s ++ [ch']
capitalizeName ch e = e & editContentsL %~ insertChar ch'
where
s = e^.to userText
ch' = if lockFlag s
then toUpper ch
else ch
@@ -122,5 +129,21 @@ capitalizeName ch s = s ++ [ch']
| isSpace c = lockFlag' cs
| otherwise = False
-- | Converts a list of lines to a widget
linesToWidget :: [String] -> Widget ()
linesToWidget = vBox . map str
linesToWidget = vBox . map (str . keepBlank)
-- | Converts a list of lines to a widget with each line horizontally
-- centered
linesToWidgetC :: [String] -> Widget ()
linesToWidgetC = vBox . map (hCenter . str . keepBlank)
-- | Fetches the text from an editor widget
userText :: Editor String () -> String
userText w = case getEditContents w of
(x:_) -> x
[] -> ""
keepBlank :: String -> String
keepBlank "" = " "
keepBlank s = s

View File

@@ -24,7 +24,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module ActionsSpec (spec) where
import Control.Monad (replicateM)
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import Lens.Micro ((^.), (&), (.~), (?~), (%~), to)
import Test.Hspec
( Spec
, context
@@ -37,9 +37,11 @@ import Test.Hspec
import Mtlstats.Actions
import Mtlstats.Types
import Mtlstats.Util
import qualified Actions.NewGameSpec as NewGame
import qualified Actions.EditStandingsSpec as EditStandings
import SpecHelpers
import qualified TypesSpec as TS
spec :: Spec
@@ -49,8 +51,6 @@ spec = describe "Mtlstats.Actions" $ do
resetYtdSpec
clearRookiesSpec
resetStandingsSpec
addCharSpec
removeCharSpec
createPlayerSpec
createGoalieSpec
editSpec
@@ -204,29 +204,6 @@ resetStandingsSpec = describe "resetStandings" $ do
it "should be reset" $
ps^.database.dbAwayGameStats `shouldBe` newGameStats
addCharSpec :: Spec
addCharSpec = describe "addChar" $
it "should add the character to the input buffer" $ let
s = newProgState
& inputBuffer .~ "foo"
& addChar 'd'
in s ^. inputBuffer `shouldBe` "food"
removeCharSpec :: Spec
removeCharSpec = describe "removeChar" $ do
context "empty" $
it "should remove the character from the input buffer" $ let
s = removeChar newProgState
in s ^. inputBuffer `shouldBe` ""
context "not empty" $
it "should remove the character from the input buffer" $ let
s = newProgState
& inputBuffer .~ "foo"
& removeChar
in s ^. inputBuffer `shouldBe` "fo"
createPlayerSpec :: Spec
createPlayerSpec = describe "createPlayer" $
it "should change the mode appropriately" $ let
@@ -422,7 +399,7 @@ backHomeSpec = describe "backHome" $ do
let
input = newProgState
& progMode.gameStateL .~ newGameState
& inputBuffer .~ "foo"
& editorW .~ mkEditor "foo"
result = backHome input
it "should set the program mode back to MainMenu" $
@@ -431,4 +408,4 @@ backHomeSpec = describe "backHome" $ do
_ -> False
it "should clear the input buffer" $
result^.inputBuffer `shouldBe` ""
result^.editorW.to userText `shouldBe` ""

29
test/SpecHelpers.hs Normal file
View File

@@ -0,0 +1,29 @@
{-
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 SpecHelpers where
import Brick.Widgets.Edit (Editor, editContentsL, editor)
import Data.Text.Zipper (gotoEOL)
import Lens.Micro ((&), (%~))
mkEditor :: String -> Editor String ()
mkEditor str = editor () (Just 1) str & editContentsL %~ gotoEOL

View File

@@ -26,6 +26,8 @@ import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Util
import SpecHelpers
spec :: Spec
spec = describe "Mtlstats.Util" $ do
nthSpec
@@ -114,7 +116,7 @@ capitalizeNameSpec :: Spec
capitalizeNameSpec = describe "capitalizeName" $ mapM_
(\(label, ch, str, expected) -> context label $
it ("should be " ++ expected) $
capitalizeName ch str `shouldBe` expected)
userText (capitalizeName ch $ mkEditor str) `shouldBe` expected)
-- label, character, string, expected
[ ( "initial lower", 'a', "", "A" )
, ( "initial upper", 'A', "", "A" )