Merge pull request #73 from mtlstats/position-shortcuts
autocompletion of player positions
This commit is contained in:
commit
a69853858d
|
@ -1,5 +1,8 @@
|
||||||
# Changelog for mtlstats
|
# Changelog for mtlstats
|
||||||
|
|
||||||
|
## current
|
||||||
|
- Added autocomplete to player position prompt
|
||||||
|
|
||||||
## 0.12.0
|
## 0.12.0
|
||||||
- Edit lifetime stats on new player/goalie creation
|
- Edit lifetime stats on new player/goalie creation
|
||||||
- Sort goalies by minutes played
|
- Sort goalies by minutes played
|
||||||
|
|
|
@ -0,0 +1,89 @@
|
||||||
|
{- |
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 1984, 1985, 2019, 2020 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/>.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
|
||||||
|
module Mtlstats.Helpers.Position
|
||||||
|
( posSearch
|
||||||
|
, posSearchExact
|
||||||
|
, posCallback
|
||||||
|
, getPositions
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets)
|
||||||
|
import Data.Char (toUpper)
|
||||||
|
import Data.List (isInfixOf)
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import qualified Data.Set as S
|
||||||
|
import Lens.Micro ((^.), to)
|
||||||
|
|
||||||
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
-- | Searches the 'Database' for all the positions used
|
||||||
|
posSearch
|
||||||
|
:: String
|
||||||
|
-- ^ The search string
|
||||||
|
-> Database
|
||||||
|
-- ^ The database
|
||||||
|
-> [(Int, String)]
|
||||||
|
-- ^ A list of result indices and their values
|
||||||
|
posSearch sStr db = filter sFunc $ zip [0..] ps
|
||||||
|
where
|
||||||
|
sFunc (_, pos) = map toUpper sStr `isInfixOf` map toUpper pos
|
||||||
|
ps = getPositions db
|
||||||
|
|
||||||
|
-- | Searches the 'Database' for an exact position
|
||||||
|
posSearchExact
|
||||||
|
:: String
|
||||||
|
-- ^ The search string
|
||||||
|
-> Database
|
||||||
|
-- ^ The database
|
||||||
|
-> Maybe Int
|
||||||
|
-- ^ The index of the result (or 'Nothing' if not found)
|
||||||
|
posSearchExact sStr db = case filter sFunc $ zip [0..] ps of
|
||||||
|
[] -> Nothing
|
||||||
|
(n,_):_ -> Just n
|
||||||
|
where
|
||||||
|
sFunc (_, pos) = sStr == pos
|
||||||
|
ps = getPositions db
|
||||||
|
|
||||||
|
-- | Builds a callback function for when a 'Player' position is
|
||||||
|
-- selected
|
||||||
|
posCallback
|
||||||
|
:: (String -> Action ())
|
||||||
|
-- ^ The raw callback function
|
||||||
|
-> Maybe Int
|
||||||
|
-- ^ The index number of the position selected or 'Nothing' if blank
|
||||||
|
-> Action ()
|
||||||
|
-- ^ The action to perform
|
||||||
|
posCallback callback = \case
|
||||||
|
Nothing -> callback ""
|
||||||
|
Just n -> do
|
||||||
|
ps <- gets (^.database.to getPositions)
|
||||||
|
let pos = fromMaybe "" $ nth n ps
|
||||||
|
callback pos
|
||||||
|
|
||||||
|
-- | Extracts a list of positions from a 'Database'
|
||||||
|
getPositions :: Database -> [String]
|
||||||
|
getPositions = do
|
||||||
|
raw <- map (^.pPosition) . (^.dbPlayers)
|
||||||
|
return $ S.toList $ S.fromList raw
|
|
@ -42,6 +42,7 @@ module Mtlstats.Prompt (
|
||||||
goalieNamePrompt,
|
goalieNamePrompt,
|
||||||
selectPlayerPrompt,
|
selectPlayerPrompt,
|
||||||
selectGoaliePrompt,
|
selectGoaliePrompt,
|
||||||
|
selectPositionPrompt,
|
||||||
playerToEditPrompt
|
playerToEditPrompt
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -56,6 +57,7 @@ import qualified UI.NCurses as C
|
||||||
|
|
||||||
import Mtlstats.Actions
|
import Mtlstats.Actions
|
||||||
import Mtlstats.Config
|
import Mtlstats.Config
|
||||||
|
import Mtlstats.Helpers.Position
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
import Mtlstats.Util
|
import Mtlstats.Util
|
||||||
|
|
||||||
|
@ -236,7 +238,7 @@ playerNamePrompt = namePrompt "Player name: " $
|
||||||
|
|
||||||
-- | Prompts for a new player's position
|
-- | Prompts for a new player's position
|
||||||
playerPosPrompt :: Prompt
|
playerPosPrompt :: Prompt
|
||||||
playerPosPrompt = ucStrPrompt "Player position: " $
|
playerPosPrompt = selectPositionPrompt "Player position: " $
|
||||||
modify . (progMode.createPlayerStateL.cpsPosition .~)
|
modify . (progMode.createPlayerStateL.cpsPosition .~)
|
||||||
|
|
||||||
-- | Prompts tor the goalie's number
|
-- | Prompts tor the goalie's number
|
||||||
|
@ -307,6 +309,24 @@ selectGoaliePrompt pStr callback = selectPrompt SelectParams
|
||||||
modify $ progMode .~ CreateGoalie cgs
|
modify $ progMode .~ CreateGoalie cgs
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Selects (or creates) a player position
|
||||||
|
selectPositionPrompt
|
||||||
|
:: String
|
||||||
|
-- ^ The 'Prompt' string
|
||||||
|
-> (String -> Action ())
|
||||||
|
-- ^ The action to perform when a value is entered
|
||||||
|
-> Prompt
|
||||||
|
selectPositionPrompt pStr callback = selectPrompt SelectParams
|
||||||
|
{ spPrompt = pStr
|
||||||
|
, spSearchHeader = "Positions:"
|
||||||
|
, spSearch = posSearch
|
||||||
|
, spSearchExact = posSearchExact
|
||||||
|
, spElemDesc = id
|
||||||
|
, spProcessChar = \ch -> (++ [toUpper ch])
|
||||||
|
, spCallback = posCallback callback
|
||||||
|
, spNotFound = callback
|
||||||
|
}
|
||||||
|
|
||||||
playerToEditPrompt :: Prompt
|
playerToEditPrompt :: Prompt
|
||||||
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
|
playerToEditPrompt = selectPlayerPrompt "Player to edit: " $
|
||||||
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
|
modify . (progMode.editPlayerStateL.epsSelectedPlayer .~)
|
||||||
|
|
|
@ -62,7 +62,7 @@ editPlayerPosPrompt
|
||||||
:: Action ()
|
:: Action ()
|
||||||
-- ^ The action to be performed upon completion
|
-- ^ The action to be performed upon completion
|
||||||
-> Prompt
|
-> Prompt
|
||||||
editPlayerPosPrompt callback = ucStrPrompt "Player position: " $ \pos -> do
|
editPlayerPosPrompt callback = selectPositionPrompt "Player position: " $ \pos -> do
|
||||||
if null pos
|
if null pos
|
||||||
then goto EPMenu
|
then goto EPMenu
|
||||||
else doEdit EPMenu $ pPosition .~ pos
|
else doEdit EPMenu $ pPosition .~ pos
|
||||||
|
|
|
@ -0,0 +1,79 @@
|
||||||
|
{-
|
||||||
|
|
||||||
|
mtlstats
|
||||||
|
Copyright (C) 1984, 1985, 2019, 2020 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 Helpers.PositionSpec (spec) where
|
||||||
|
|
||||||
|
import Lens.Micro ((&), (.~))
|
||||||
|
import Test.Hspec (Spec, context, describe, it, shouldBe)
|
||||||
|
|
||||||
|
import Mtlstats.Helpers.Position
|
||||||
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Position" $ do
|
||||||
|
posSearchSpec
|
||||||
|
posSearchExactSpec
|
||||||
|
getPositionsSpec
|
||||||
|
|
||||||
|
posSearchSpec :: Spec
|
||||||
|
posSearchSpec = describe "posSearch" $ mapM_
|
||||||
|
(\(sStr, expected) -> context ("search string: " ++ show sStr) $
|
||||||
|
it ("should be " ++ show expected) $
|
||||||
|
posSearch sStr db `shouldBe` expected)
|
||||||
|
[ ( "fOo"
|
||||||
|
, [ ( 2, "foo" )
|
||||||
|
]
|
||||||
|
)
|
||||||
|
, ( "A"
|
||||||
|
, [ ( 0, "bar" )
|
||||||
|
, ( 1, "baz" )
|
||||||
|
]
|
||||||
|
)
|
||||||
|
]
|
||||||
|
|
||||||
|
posSearchExactSpec :: Spec
|
||||||
|
posSearchExactSpec = describe "posSearchExact" $ mapM_
|
||||||
|
(\(input, expected) -> context ("input: " ++ show input) $
|
||||||
|
it ("should be " ++ show expected) $
|
||||||
|
posSearchExact input db `shouldBe` expected)
|
||||||
|
|
||||||
|
-- input, expected
|
||||||
|
[ ( "foo", Just 2 )
|
||||||
|
, ( "FOO", Nothing )
|
||||||
|
, ( "bar", Just 0 )
|
||||||
|
, ( "baz", Just 1 )
|
||||||
|
, ( "a", Nothing )
|
||||||
|
, ( "quux", Nothing )
|
||||||
|
]
|
||||||
|
|
||||||
|
getPositionsSpec :: Spec
|
||||||
|
getPositionsSpec = describe "getPositions" $ let
|
||||||
|
expected = ["bar", "baz", "foo"]
|
||||||
|
in it ("should be " ++ show expected) $
|
||||||
|
getPositions db `shouldBe` expected
|
||||||
|
|
||||||
|
db :: Database
|
||||||
|
db = newDatabase & dbPlayers .~
|
||||||
|
[ newPlayer 2 "Joe" "foo"
|
||||||
|
, newPlayer 3 "Bob" "bar"
|
||||||
|
, newPlayer 5 "Bill" "foo"
|
||||||
|
, newPlayer 8 "Ed" "baz"
|
||||||
|
]
|
|
@ -25,8 +25,10 @@ import Test.Hspec (Spec, describe)
|
||||||
|
|
||||||
import qualified Helpers.GoalieSpec as Goalie
|
import qualified Helpers.GoalieSpec as Goalie
|
||||||
import qualified Helpers.PlayerSpec as Player
|
import qualified Helpers.PlayerSpec as Player
|
||||||
|
import qualified Helpers.PositionSpec as Position
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = describe "Helper" $ do
|
spec = describe "Helper" $ do
|
||||||
Player.spec
|
Player.spec
|
||||||
Goalie.spec
|
Goalie.spec
|
||||||
|
Position.spec
|
||||||
|
|
Loading…
Reference in New Issue
Block a user