Merge pull request #42 from mtlstats/lower-case

allow lower case player names
This commit is contained in:
Jonathan Lamothe 2019-11-30 21:53:07 -05:00 committed by GitHub
commit 9e6b71c464
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
5 changed files with 41 additions and 27 deletions

View File

@ -2,6 +2,7 @@
## current ## current
- Bugfix: removed quotation marks from goalie names in report - Bugfix: removed quotation marks from goalie names in report
- Allow lower case player names
## 0.7.0 ## 0.7.0
- Shortened views to fit within 25 lines - Shortened views to fit within 25 lines

View File

@ -28,6 +28,7 @@ module Mtlstats.Prompt (
promptControllerWith, promptControllerWith,
promptController, promptController,
strPrompt, strPrompt,
ucStrPrompt,
numPrompt, numPrompt,
selectPrompt, selectPrompt,
-- * Individual prompts -- * Individual prompts
@ -46,7 +47,7 @@ import Control.Monad.Extra (whenJust)
import Control.Monad.Trans.State (gets, modify) import Control.Monad.Trans.State (gets, modify)
import Data.Char (isDigit, toUpper) import Data.Char (isDigit, toUpper)
import Data.Foldable (forM_) import Data.Foldable (forM_)
import Lens.Micro ((^.), (&), (.~), (?~)) import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import Lens.Micro.Extras (view) import Lens.Micro.Extras (view)
import Text.Read (readMaybe) import Text.Read (readMaybe)
import qualified UI.NCurses as C import qualified UI.NCurses as C
@ -68,10 +69,8 @@ promptHandler p (C.EventCharacter '\n') = do
val <- gets $ view inputBuffer val <- gets $ view inputBuffer
modify $ inputBuffer .~ "" modify $ inputBuffer .~ ""
promptAction p val promptAction p val
promptHandler p (C.EventCharacter c) = let promptHandler p (C.EventCharacter c) =
c' = toUpper c modify $ inputBuffer %~ promptProcessChar p c
in when (promptCharCheck p c') $
modify $ addChar c'
promptHandler _ (C.EventSpecialKey C.KeyBackspace) = promptHandler _ (C.EventSpecialKey C.KeyBackspace) =
modify removeChar modify removeChar
promptHandler p (C.EventSpecialKey k) = promptHandler p (C.EventSpecialKey k) =
@ -112,11 +111,21 @@ strPrompt
-> Prompt -> Prompt
strPrompt pStr act = Prompt strPrompt pStr act = Prompt
{ promptDrawer = drawSimplePrompt pStr { promptDrawer = drawSimplePrompt pStr
, promptCharCheck = const True , promptProcessChar = \ch -> (++ [ch])
, promptAction = act , promptAction = act
, promptSpecialKey = const $ return () , promptSpecialKey = const $ return ()
} }
-- | Creates an upper case string prompt
ucStrPrompt
:: String
-- ^ The prompt string
-> (String -> Action ())
-- ^ The callback function for the result
-> Prompt
ucStrPrompt pStr act = (ucStrPrompt pStr act)
{ promptProcessChar = \ch -> (++ [toUpper ch]) }
-- | Builds a numeric prompt -- | Builds a numeric prompt
numPrompt numPrompt
:: String :: String
@ -126,7 +135,9 @@ numPrompt
-> Prompt -> Prompt
numPrompt pStr act = Prompt numPrompt pStr act = Prompt
{ promptDrawer = drawSimplePrompt pStr { promptDrawer = drawSimplePrompt pStr
, promptCharCheck = isDigit , promptProcessChar = \ch str -> if isDigit ch
then str ++ [ch]
else str
, promptAction = \inStr -> forM_ (readMaybe inStr) act , promptAction = \inStr -> forM_ (readMaybe inStr) act
, promptSpecialKey = const $ return () , promptSpecialKey = const $ return ()
} }
@ -146,7 +157,7 @@ selectPrompt params = Prompt
in "F" ++ show n ++ ") " ++ desc) in "F" ++ show n ++ ") " ++ desc)
results results
C.moveCursor row col C.moveCursor row col
, promptCharCheck = const True , promptProcessChar = \ch -> (++[ch])
, promptAction = \sStr -> if null sStr , promptAction = \sStr -> if null sStr
then spCallback params Nothing then spCallback params Nothing
else do else do
@ -180,7 +191,7 @@ playerNamePrompt = strPrompt "Player name: " $
-- | Prompts for a new player's position -- | Prompts for a new player's position
playerPosPrompt :: Prompt playerPosPrompt :: Prompt
playerPosPrompt = strPrompt "Player position: " $ playerPosPrompt = ucStrPrompt "Player position: " $
modify . (progMode.createPlayerStateL.cpsPosition .~) modify . (progMode.createPlayerStateL.cpsPosition .~)
-- | Prompts tor the goalie's number -- | Prompts tor the goalie's number

View File

@ -51,7 +51,7 @@ editPlayerNamePrompt = strPrompt "Player name: " $
-- | Prompt to edit a player's position -- | Prompt to edit a player's position
editPlayerPosPrompt :: Prompt editPlayerPosPrompt :: Prompt
editPlayerPosPrompt = strPrompt "Player position: " $ editPlayerPosPrompt = ucStrPrompt "Player position: " $
editPlayer . (pPosition .~) editPlayer . (pPosition .~)
-- | Prompt to edit a player's year-to-date goals -- | Prompt to edit a player's year-to-date goals

View File

@ -192,6 +192,7 @@ import Data.Aeson
, (.!=) , (.!=)
, (.=) , (.=)
) )
import Data.Char (toUpper)
import Data.List (isInfixOf) import Data.List (isInfixOf)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (listToMaybe) import Data.Maybe (listToMaybe)
@ -601,8 +602,8 @@ instance ToJSON GameStats where
data Prompt = Prompt data Prompt = Prompt
{ promptDrawer :: ProgState -> C.Update () { promptDrawer :: ProgState -> C.Update ()
-- ^ Draws the prompt to the screen -- ^ Draws the prompt to the screen
, promptCharCheck :: Char -> Bool , promptProcessChar :: Char -> String -> String
-- ^ Determines whether or not the character is valid -- ^ Modifies the string based on the character entered
, promptAction :: String -> Action () , promptAction :: String -> Action ()
-- ^ Action to perform when the value is entered -- ^ Action to perform when the value is entered
, promptSpecialKey :: C.Key -> Action () , promptSpecialKey :: C.Key -> Action ()
@ -904,7 +905,7 @@ playerSearch
-- ^ The matching players with their index numbers -- ^ The matching players with their index numbers
playerSearch sStr = playerSearch sStr =
filter match . zip [0..] filter match . zip [0..]
where match (_, p) = sStr `isInfixOf` (p^.pName) where match (_, p) = map toUpper sStr `isInfixOf` map toUpper (p^.pName)
-- | Searches for a player by exact match on name -- | Searches for a player by exact match on name
playerSearchExact playerSearchExact
@ -967,8 +968,9 @@ goalieSearch
-- ^ The list to search -- ^ The list to search
-> [(Int, Goalie)] -> [(Int, Goalie)]
-- ^ The search results with their corresponding index numbers -- ^ The search results with their corresponding index numbers
goalieSearch sStr = filter (\(_, goalie) -> sStr `isInfixOf` (goalie^.gName)) . goalieSearch sStr =
zip [0..] filter match . zip [0..]
where match (_, g) = map toUpper sStr `isInfixOf` map toUpper (g^.gName)
-- | Searches a list of goalies for an exact match -- | Searches a list of goalies for an exact match
goalieSearchExact goalieSearchExact

View File

@ -591,7 +591,7 @@ playerSearchSpec = describe "playerSearch" $ mapM_
ps = [joe, bob, steve] ps = [joe, bob, steve]
in playerSearch sStr ps `shouldBe` expected) in playerSearch sStr ps `shouldBe` expected)
-- search, result -- search, result
[ ( "Joe", [(0, joe)] ) [ ( "joe", [(0, joe)] )
, ( "o", [(0, joe), (1, bob)] ) , ( "o", [(0, joe), (1, bob)] )
, ( "e", [(0, joe), (2, steve)] ) , ( "e", [(0, joe), (2, steve)] )
, ( "x", [] ) , ( "x", [] )
@ -725,8 +725,8 @@ goalieSearchSpec = describe "goalieSearch" $ do
goalieSearch "x" goalies `shouldBe` [] goalieSearch "x" goalies `shouldBe` []
context "exact match" $ context "exact match" $
it "should return Steve" $ it "should return Bob" $
goalieSearch "Bob" goalies `shouldBe` [result 1] goalieSearch "bob" goalies `shouldBe` [result 1]
goalieSearchExactSpec :: Spec goalieSearchExactSpec :: Spec
goalieSearchExactSpec = describe "goalieSearchExact" $ do goalieSearchExactSpec = describe "goalieSearchExact" $ do