commit
3c0e690ed3
|
@ -3,6 +3,7 @@
|
||||||
## current
|
## current
|
||||||
- Ask for database to load on start-up
|
- Ask for database to load on start-up
|
||||||
- Add page break to report file
|
- Add page break to report file
|
||||||
|
- Implemented player/goalie deletion
|
||||||
|
|
||||||
## 0.14.0
|
## 0.14.0
|
||||||
- Fixed a bug that was causing shutouts to not be recorded
|
- Fixed a bug that was causing shutouts to not be recorded
|
||||||
|
|
|
@ -23,10 +23,13 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Mtlstats.Control.EditGoalie (editGoalieC) where
|
module Mtlstats.Control.EditGoalie (editGoalieC) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.), (.~), (%~))
|
||||||
import UI.NCurses as C
|
import UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Actions
|
||||||
|
import Mtlstats.Handlers
|
||||||
import Mtlstats.Helpers.Goalie
|
import Mtlstats.Helpers.Goalie
|
||||||
import Mtlstats.Menu
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Menu.EditGoalie
|
import Mtlstats.Menu.EditGoalie
|
||||||
|
@ -52,6 +55,7 @@ editC cb =
|
||||||
EGName -> nameC
|
EGName -> nameC
|
||||||
EGYtd -> ytdMenuC
|
EGYtd -> ytdMenuC
|
||||||
EGLifetime -> lifetimeMenuC
|
EGLifetime -> lifetimeMenuC
|
||||||
|
EGDelete -> deleteC
|
||||||
EGYtdGames b -> ytdGamesC b
|
EGYtdGames b -> ytdGamesC b
|
||||||
EGYtdMins b -> ytdMinsC b
|
EGYtdMins b -> ytdMinsC b
|
||||||
EGYtdGoals b -> ytdGoalsC b
|
EGYtdGoals b -> ytdGoalsC b
|
||||||
|
@ -83,6 +87,38 @@ ytdMenuC _ = menuControllerWith header editGoalieYtdMenu
|
||||||
lifetimeMenuC :: Action () -> Controller
|
lifetimeMenuC :: Action () -> Controller
|
||||||
lifetimeMenuC _ = menuControllerWith header editGoalieLtMenu
|
lifetimeMenuC _ = menuControllerWith header editGoalieLtMenu
|
||||||
|
|
||||||
|
deleteC :: Action () -> Controller
|
||||||
|
deleteC _ = Controller
|
||||||
|
|
||||||
|
{ drawController = \s -> do
|
||||||
|
|
||||||
|
C.drawString $ let
|
||||||
|
|
||||||
|
hdr = fromMaybe [] $ do
|
||||||
|
gid <- s^.progMode.editGoalieStateL.egsSelectedGoalie
|
||||||
|
goalie <- nth gid $ s^.database.dbGoalies
|
||||||
|
Just $ "Goalie: " ++ goalieDetails goalie ++ "\n\n"
|
||||||
|
|
||||||
|
in hdr ++ "Are you sure you want to delete this goalie? (Y/N)"
|
||||||
|
|
||||||
|
return C.CursorInvisible
|
||||||
|
|
||||||
|
, handleController = \e -> do
|
||||||
|
|
||||||
|
case ynHandler e of
|
||||||
|
|
||||||
|
Just True -> do
|
||||||
|
gets (^.progMode.editGoalieStateL.egsSelectedGoalie) >>= mapM_
|
||||||
|
(\gid -> modify $ database.dbGoalies %~ dropNth gid)
|
||||||
|
modify edit
|
||||||
|
|
||||||
|
Just False -> modify $ progMode.editGoalieStateL.egsMode .~ EGMenu
|
||||||
|
Nothing -> return ()
|
||||||
|
|
||||||
|
return True
|
||||||
|
|
||||||
|
}
|
||||||
|
|
||||||
ytdGamesC :: Bool -> Action () -> Controller
|
ytdGamesC :: Bool -> Action () -> Controller
|
||||||
ytdGamesC = curry $ promptController .
|
ytdGamesC = curry $ promptController .
|
||||||
uncurry editGoalieYtdGamesPrompt
|
uncurry editGoalieYtdGamesPrompt
|
||||||
|
|
|
@ -21,10 +21,13 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Mtlstats.Control.EditPlayer (editPlayerC) where
|
module Mtlstats.Control.EditPlayer (editPlayerC) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.State (gets, modify)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.), (.~), (%~))
|
||||||
import qualified UI.NCurses as C
|
import qualified UI.NCurses as C
|
||||||
|
|
||||||
|
import Mtlstats.Actions
|
||||||
|
import Mtlstats.Handlers
|
||||||
import Mtlstats.Helpers.Player
|
import Mtlstats.Helpers.Player
|
||||||
import Mtlstats.Menu
|
import Mtlstats.Menu
|
||||||
import Mtlstats.Menu.EditPlayer
|
import Mtlstats.Menu.EditPlayer
|
||||||
|
@ -45,6 +48,7 @@ editPlayerC eps
|
||||||
EPPosition -> positionC
|
EPPosition -> positionC
|
||||||
EPYtd -> ytdC
|
EPYtd -> ytdC
|
||||||
EPLifetime -> lifetimeC
|
EPLifetime -> lifetimeC
|
||||||
|
EPDelete -> deleteC
|
||||||
EPYtdGoals b -> ytdGoalsC b
|
EPYtdGoals b -> ytdGoalsC b
|
||||||
EPYtdAssists b -> ytdAssistsC b
|
EPYtdAssists b -> ytdAssistsC b
|
||||||
EPYtdPMin -> ytdPMinC
|
EPYtdPMin -> ytdPMinC
|
||||||
|
@ -74,6 +78,38 @@ ytdC _ = menuControllerWith header editPlayerYtdMenu
|
||||||
lifetimeC :: Action () -> Controller
|
lifetimeC :: Action () -> Controller
|
||||||
lifetimeC _ = menuControllerWith header editPlayerLtMenu
|
lifetimeC _ = menuControllerWith header editPlayerLtMenu
|
||||||
|
|
||||||
|
deleteC :: Action () -> Controller
|
||||||
|
deleteC _ = Controller
|
||||||
|
|
||||||
|
{ drawController = \s -> do
|
||||||
|
|
||||||
|
C.drawString $ let
|
||||||
|
|
||||||
|
hdr = fromMaybe [] $ do
|
||||||
|
pid <- s^.progMode.editPlayerStateL.epsSelectedPlayer
|
||||||
|
player <- nth pid $ s^.database.dbPlayers
|
||||||
|
Just $ "Player: " ++ playerDetails player ++ "\n\n"
|
||||||
|
|
||||||
|
in hdr ++ "Are you sure you want to delete this player? (Y/N)"
|
||||||
|
|
||||||
|
return C.CursorInvisible
|
||||||
|
|
||||||
|
, handleController = \e -> do
|
||||||
|
|
||||||
|
case ynHandler e of
|
||||||
|
|
||||||
|
Just True -> do
|
||||||
|
gets (^.progMode.editPlayerStateL.epsSelectedPlayer) >>= mapM_
|
||||||
|
(\pid -> modify $ database.dbPlayers %~ dropNth pid)
|
||||||
|
modify edit
|
||||||
|
|
||||||
|
Just False -> modify $ progMode.editPlayerStateL.epsMode .~ EPMenu
|
||||||
|
Nothing -> return ()
|
||||||
|
|
||||||
|
return True
|
||||||
|
|
||||||
|
}
|
||||||
|
|
||||||
ytdGoalsC :: Bool -> Action () -> Controller
|
ytdGoalsC :: Bool -> Action () -> Controller
|
||||||
ytdGoalsC batchMode callback = promptController $
|
ytdGoalsC batchMode callback = promptController $
|
||||||
editPlayerYtdGoalsPrompt batchMode callback
|
editPlayerYtdGoalsPrompt batchMode callback
|
||||||
|
|
|
@ -44,6 +44,7 @@ editGoalieMenu = Menu "EDIT GOALTENDER" () $ map
|
||||||
, ( 'D', "ACTIVE FLAG", toggleActive )
|
, ( 'D', "ACTIVE FLAG", toggleActive )
|
||||||
, ( 'E', "YTD STATS", set EGYtd )
|
, ( 'E', "YTD STATS", set EGYtd )
|
||||||
, ( 'F', "LIFETIME STATS", set EGLifetime )
|
, ( 'F', "LIFETIME STATS", set EGLifetime )
|
||||||
|
, ( 'G', "DELETE RECORD", set EGDelete )
|
||||||
, ( 'R', "RETURN TO EDIT MENU", edit )
|
, ( 'R', "RETURN TO EDIT MENU", edit )
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
|
@ -45,6 +45,7 @@ editPlayerMenu = Menu "EDIT PLAYER" () $ map
|
||||||
, ( 'E', "ACTIVE FLAG", toggleActive )
|
, ( 'E', "ACTIVE FLAG", toggleActive )
|
||||||
, ( 'F', "YTD STATS", set EPYtd )
|
, ( 'F', "YTD STATS", set EPYtd )
|
||||||
, ( 'G', "LIFETIME STATS", set EPLifetime )
|
, ( 'G', "LIFETIME STATS", set EPLifetime )
|
||||||
|
, ( 'H', "DELETE RECORD", set EPDelete )
|
||||||
, ( 'R', "RETURN TO EDIT MENU", edit )
|
, ( 'R', "RETURN TO EDIT MENU", edit )
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
|
@ -378,6 +378,7 @@ data EditPlayerMode
|
||||||
| EPPosition
|
| EPPosition
|
||||||
| EPYtd
|
| EPYtd
|
||||||
| EPLifetime
|
| EPLifetime
|
||||||
|
| EPDelete
|
||||||
| EPYtdGoals Bool
|
| EPYtdGoals Bool
|
||||||
| EPYtdAssists Bool
|
| EPYtdAssists Bool
|
||||||
| EPYtdPMin
|
| EPYtdPMin
|
||||||
|
@ -403,6 +404,7 @@ data EditGoalieMode
|
||||||
| EGName
|
| EGName
|
||||||
| EGYtd
|
| EGYtd
|
||||||
| EGLifetime
|
| EGLifetime
|
||||||
|
| EGDelete
|
||||||
| EGYtdGames Bool
|
| EGYtdGames Bool
|
||||||
| EGYtdMins Bool
|
| EGYtdMins Bool
|
||||||
| EGYtdGoals Bool
|
| EGYtdGoals Bool
|
||||||
|
|
|
@ -22,6 +22,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
module Mtlstats.Util
|
module Mtlstats.Util
|
||||||
( nth
|
( nth
|
||||||
, modifyNth
|
, modifyNth
|
||||||
|
, dropNth
|
||||||
, updateMap
|
, updateMap
|
||||||
, slice
|
, slice
|
||||||
, capitalizeName
|
, capitalizeName
|
||||||
|
@ -56,6 +57,18 @@ modifyNth n f = zipWith
|
||||||
(\i x -> if i == n then f x else x)
|
(\i x -> if i == n then f x else x)
|
||||||
[0..]
|
[0..]
|
||||||
|
|
||||||
|
-- | Attempt to drop the nth element from a list
|
||||||
|
dropNth
|
||||||
|
:: Int
|
||||||
|
-- ^ The index of the element to drop
|
||||||
|
-> [a]
|
||||||
|
-- ^ The list to be modified
|
||||||
|
-> [a]
|
||||||
|
-- ^ The modified list
|
||||||
|
dropNth n = foldr
|
||||||
|
(\(i, x) acc -> if i == n then acc else x : acc)
|
||||||
|
[] . zip [0..]
|
||||||
|
|
||||||
-- | Modify a value indexed by a given key in a map using a default
|
-- | Modify a value indexed by a given key in a map using a default
|
||||||
-- initial value if not present
|
-- initial value if not present
|
||||||
updateMap
|
updateMap
|
||||||
|
|
|
@ -30,6 +30,7 @@ spec :: Spec
|
||||||
spec = describe "Mtlstats.Util" $ do
|
spec = describe "Mtlstats.Util" $ do
|
||||||
nthSpec
|
nthSpec
|
||||||
modifyNthSpec
|
modifyNthSpec
|
||||||
|
dropNthSpec
|
||||||
updateMapSpec
|
updateMapSpec
|
||||||
sliceSpec
|
sliceSpec
|
||||||
capitalizeNameSpec
|
capitalizeNameSpec
|
||||||
|
@ -64,6 +65,20 @@ modifyNthSpec = describe "modifyNth" $ do
|
||||||
it "should not modify the value" $
|
it "should not modify the value" $
|
||||||
modifyNth (-1) succ list `shouldBe` [1, 2, 3]
|
modifyNth (-1) succ list `shouldBe` [1, 2, 3]
|
||||||
|
|
||||||
|
dropNthSpec :: Spec
|
||||||
|
dropNthSpec = describe "dropNth" $ mapM_
|
||||||
|
|
||||||
|
(\(label, n, expected) ->
|
||||||
|
context label $
|
||||||
|
it ("should be " ++ show expected) $
|
||||||
|
dropNth n list `shouldBe` expected)
|
||||||
|
|
||||||
|
[ ( "out of bounds", 1, ["foo", "baz"] )
|
||||||
|
, ( "in bounds", 3, list )
|
||||||
|
]
|
||||||
|
|
||||||
|
where list = ["foo", "bar", "baz"]
|
||||||
|
|
||||||
updateMapSpec :: Spec
|
updateMapSpec :: Spec
|
||||||
updateMapSpec = describe "updateMap" $ do
|
updateMapSpec = describe "updateMap" $ do
|
||||||
let
|
let
|
||||||
|
|
Loading…
Reference in New Issue
Block a user