implemented posCallback
This commit is contained in:
@@ -19,6 +19,8 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
|
||||||
module Mtlstats.Helpers.Position
|
module Mtlstats.Helpers.Position
|
||||||
( posSearch
|
( posSearch
|
||||||
, posSearchExact
|
, posSearchExact
|
||||||
@@ -26,12 +28,15 @@ module Mtlstats.Helpers.Position
|
|||||||
, getPositions
|
, getPositions
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets)
|
||||||
import Data.Char (toUpper)
|
import Data.Char (toUpper)
|
||||||
import Data.List (isInfixOf)
|
import Data.List (isInfixOf)
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.), to)
|
||||||
|
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
|
import Mtlstats.Util
|
||||||
|
|
||||||
-- | Searches the 'Database' for all the positions used
|
-- | Searches the 'Database' for all the positions used
|
||||||
posSearch
|
posSearch
|
||||||
@@ -70,7 +75,12 @@ posCallback
|
|||||||
-- ^ The index number of the position selected or 'Nothing' if blank
|
-- ^ The index number of the position selected or 'Nothing' if blank
|
||||||
-> Action ()
|
-> Action ()
|
||||||
-- ^ The action to perform
|
-- ^ The action to perform
|
||||||
posCallback = undefined
|
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'
|
-- | Extracts a list of positions from a 'Database'
|
||||||
getPositions :: Database -> [String]
|
getPositions :: Database -> [String]
|
||||||
|
|||||||
Reference in New Issue
Block a user