commit
28b1fa0e06
|
@ -2,6 +2,7 @@
|
|||
|
||||
## current
|
||||
- Added autocomplete to player position prompt
|
||||
- Don't prompt for lifetime stats on rookie player/goalie creation
|
||||
|
||||
## 0.12.0
|
||||
- Edit lifetime stats on new player/goalie creation
|
||||
|
|
|
@ -161,11 +161,13 @@ editSelectedGoalie f s = fromMaybe s $ do
|
|||
addPlayer :: ProgState -> ProgState
|
||||
addPlayer s = fromMaybe s $ do
|
||||
let cps = s^.progMode.createPlayerStateL
|
||||
num <- cps^.cpsNumber
|
||||
num <- cps^.cpsNumber
|
||||
rFlag <- cps^.cpsRookieFlag
|
||||
let
|
||||
name = cps^.cpsName
|
||||
pos = cps^.cpsPosition
|
||||
player = newPlayer num name pos
|
||||
& pRookie .~ rFlag
|
||||
Just $ s & database.dbPlayers
|
||||
%~ (++[player])
|
||||
|
||||
|
@ -173,10 +175,12 @@ addPlayer s = fromMaybe s $ do
|
|||
addGoalie :: ProgState -> ProgState
|
||||
addGoalie s = fromMaybe s $ do
|
||||
let cgs = s^.progMode.createGoalieStateL
|
||||
num <- cgs^.cgsNumber
|
||||
num <- cgs^.cgsNumber
|
||||
rFlag <- cgs^.cgsRookieFlag
|
||||
let
|
||||
name = cgs^.cgsName
|
||||
goalie = newGoalie num name
|
||||
& gRookie .~ rFlag
|
||||
Just $ s & database.dbGoalies
|
||||
%~ (++[goalie])
|
||||
|
||||
|
|
|
@ -21,13 +21,12 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||
|
||||
module Mtlstats.Control.CreateGoalie (createGoalieC) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import Control.Monad.Trans.State (gets, modify)
|
||||
import Data.Maybe (fromJust)
|
||||
import Lens.Micro ((^.), (.~), (?~), (%~), to)
|
||||
import qualified UI.NCurses as C
|
||||
|
||||
import Mtlstats.Actions
|
||||
import Mtlstats.Format
|
||||
import Mtlstats.Handlers
|
||||
import Mtlstats.Prompt
|
||||
import Mtlstats.Types
|
||||
|
@ -35,23 +34,24 @@ import Mtlstats.Types
|
|||
-- | Handles goalie creation
|
||||
createGoalieC :: CreateGoalieState -> Controller
|
||||
createGoalieC cgs
|
||||
| null $ cgs^.cgsNumber = getGoalieNumC
|
||||
| null $ cgs^.cgsName = getGoalieNameC
|
||||
| otherwise = confirmCreateGoalieC
|
||||
| null $ cgs^.cgsNumber = getGoalieNumC
|
||||
| null $ cgs^.cgsName = getGoalieNameC
|
||||
| null $ cgs^.cgsRookieFlag = getRookieFlagC
|
||||
| otherwise = confirmCreateGoalieC
|
||||
|
||||
getGoalieNumC :: Controller
|
||||
getGoalieNumC = Controller
|
||||
{ drawController = drawPrompt goalieNumPrompt
|
||||
, handleController = \e -> do
|
||||
promptHandler goalieNumPrompt e
|
||||
return True
|
||||
}
|
||||
getGoalieNumC = promptController goalieNumPrompt
|
||||
|
||||
getGoalieNameC :: Controller
|
||||
getGoalieNameC = Controller
|
||||
{ drawController = drawPrompt goalieNamePrompt
|
||||
getGoalieNameC = promptController goalieNamePrompt
|
||||
|
||||
getRookieFlagC :: Controller
|
||||
getRookieFlagC = Controller
|
||||
{ drawController = const $ do
|
||||
C.drawString "Is this goalie a rookie? (Y/N)"
|
||||
return C.CursorInvisible
|
||||
, handleController = \e -> do
|
||||
promptHandler goalieNamePrompt e
|
||||
modify $ progMode.createGoalieStateL.cgsRookieFlag .~ ynHandler e
|
||||
return True
|
||||
}
|
||||
|
||||
|
@ -60,25 +60,32 @@ confirmCreateGoalieC = Controller
|
|||
{ drawController = \s -> do
|
||||
let cgs = s^.progMode.createGoalieStateL
|
||||
C.drawString $ unlines
|
||||
[ "Goalie number: " ++ show (fromJust $ cgs^.cgsNumber)
|
||||
, " Goalie name: " ++ cgs^.cgsName
|
||||
, ""
|
||||
, "Create goalie: are you sure? (Y/N)"
|
||||
]
|
||||
$ labelTable
|
||||
[ ( "Goalie number", maybe "?" show $ cgs^.cgsNumber )
|
||||
, ( "Goalie name", cgs^.cgsName )
|
||||
, ( "Rookie", maybe "?" show $ cgs^.cgsRookieFlag )
|
||||
]
|
||||
++ [ ""
|
||||
, "Create goalie: are you sure? (Y/N)"
|
||||
]
|
||||
return C.CursorInvisible
|
||||
, handleController = \e -> do
|
||||
cgs <- gets (^.progMode.createGoalieStateL)
|
||||
let
|
||||
success = cgs^.cgsSuccessCallback
|
||||
failure = cgs^.cgsFailureCallback
|
||||
case ynHandler e of
|
||||
Just True -> do
|
||||
gid <- gets (^.database.dbGoalies.to length)
|
||||
cb <- gets (^.progMode.createGoalieStateL.cgsSuccessCallback)
|
||||
modify
|
||||
$ (progMode.editGoalieStateL
|
||||
let rookie = cgs^.cgsRookieFlag == Just True
|
||||
modify addGoalie
|
||||
if rookie
|
||||
then success
|
||||
else modify $ progMode.editGoalieStateL
|
||||
%~ (egsSelectedGoalie ?~ gid)
|
||||
. (egsMode .~ EGLtGames True)
|
||||
. (egsCallback .~ cb))
|
||||
. addGoalie
|
||||
Just False ->
|
||||
join $ gets (^.progMode.createGoalieStateL.cgsFailureCallback)
|
||||
Nothing -> return ()
|
||||
. (egsMode .~ EGLtGames True)
|
||||
. (egsCallback .~ success)
|
||||
Just False -> failure
|
||||
Nothing -> return ()
|
||||
return True
|
||||
}
|
||||
|
|
|
@ -21,13 +21,12 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||
|
||||
module Mtlstats.Control.CreatePlayer (createPlayerC) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import Control.Monad.Trans.State (gets, modify)
|
||||
import Data.Maybe (fromJust)
|
||||
import Lens.Micro ((^.), (.~), (?~), (%~), to)
|
||||
import qualified UI.NCurses as C
|
||||
|
||||
import Mtlstats.Actions
|
||||
import Mtlstats.Format
|
||||
import Mtlstats.Handlers
|
||||
import Mtlstats.Prompt
|
||||
import Mtlstats.Types
|
||||
|
@ -35,32 +34,28 @@ import Mtlstats.Types
|
|||
-- | Handles player creation
|
||||
createPlayerC :: CreatePlayerState -> Controller
|
||||
createPlayerC cps
|
||||
| null $ cps^.cpsNumber = getPlayerNumC
|
||||
| null $ cps^.cpsName = getPlayerNameC
|
||||
| null $ cps^.cpsPosition = getPlayerPosC
|
||||
| otherwise = confirmCreatePlayerC
|
||||
| null $ cps^.cpsNumber = getPlayerNumC
|
||||
| null $ cps^.cpsName = getPlayerNameC
|
||||
| null $ cps^.cpsPosition = getPlayerPosC
|
||||
| null $ cps^.cpsRookieFlag = getRookieFlagC
|
||||
| otherwise = confirmCreatePlayerC
|
||||
|
||||
getPlayerNumC :: Controller
|
||||
getPlayerNumC = Controller
|
||||
{ drawController = drawPrompt playerNumPrompt
|
||||
, handleController = \e -> do
|
||||
promptHandler playerNumPrompt e
|
||||
return True
|
||||
}
|
||||
getPlayerNumC = promptController playerNumPrompt
|
||||
|
||||
getPlayerNameC :: Controller
|
||||
getPlayerNameC = Controller
|
||||
{ drawController = drawPrompt playerNamePrompt
|
||||
, handleController = \e -> do
|
||||
promptHandler playerNamePrompt e
|
||||
return True
|
||||
}
|
||||
getPlayerNameC = promptController playerNamePrompt
|
||||
|
||||
getPlayerPosC :: Controller
|
||||
getPlayerPosC = Controller
|
||||
{ drawController = drawPrompt playerPosPrompt
|
||||
getPlayerPosC = promptController playerPosPrompt
|
||||
|
||||
getRookieFlagC :: Controller
|
||||
getRookieFlagC = Controller
|
||||
{ drawController = const $ do
|
||||
C.drawString "Is this player a rookie? (Y/N)"
|
||||
return C.CursorInvisible
|
||||
, handleController = \e -> do
|
||||
promptHandler playerPosPrompt e
|
||||
modify $ progMode.createPlayerStateL.cpsRookieFlag .~ ynHandler e
|
||||
return True
|
||||
}
|
||||
|
||||
|
@ -68,24 +63,34 @@ confirmCreatePlayerC :: Controller
|
|||
confirmCreatePlayerC = Controller
|
||||
{ drawController = \s -> do
|
||||
let cps = s^.progMode.createPlayerStateL
|
||||
C.drawString $ " Player number: " ++ show (fromJust $ cps^.cpsNumber) ++ "\n"
|
||||
C.drawString $ " Player name: " ++ cps^.cpsName ++ "\n"
|
||||
C.drawString $ "Player position: " ++ cps^.cpsPosition ++ "\n\n"
|
||||
C.drawString "Create player: are you sure? (Y/N)"
|
||||
C.drawString $ unlines
|
||||
$ labelTable
|
||||
[ ( "Player number", maybe "?" show $ cps^.cpsNumber )
|
||||
, ( "Player name", cps^.cpsName )
|
||||
, ( "Player position", cps^.cpsPosition )
|
||||
, ( "Rookie", maybe "?" show $ cps^.cpsRookieFlag )
|
||||
]
|
||||
++ [ ""
|
||||
, "Create player: are you sure? (Y/N)"
|
||||
]
|
||||
return C.CursorInvisible
|
||||
, handleController = \e -> do
|
||||
cps <- gets (^.progMode.createPlayerStateL)
|
||||
let
|
||||
success = cps^.cpsSuccessCallback
|
||||
failure = cps^.cpsFailureCallback
|
||||
case ynHandler e of
|
||||
Just True -> do
|
||||
pid <- gets (^.database.dbPlayers.to length)
|
||||
cb <- gets (^.progMode.createPlayerStateL.cpsSuccessCallback)
|
||||
modify
|
||||
$ (progMode.editPlayerStateL
|
||||
let rookie = cps^.cpsRookieFlag == Just True
|
||||
modify addPlayer
|
||||
if rookie
|
||||
then success
|
||||
else modify $ progMode.editPlayerStateL
|
||||
%~ (epsSelectedPlayer ?~ pid)
|
||||
. (epsMode .~ EPLtGoals True)
|
||||
. (epsCallback .~ cb))
|
||||
. addPlayer
|
||||
Just False ->
|
||||
join $ gets (^.progMode.createPlayerStateL.cpsFailureCallback)
|
||||
. (epsMode .~ EPLtGoals True)
|
||||
. (epsCallback .~ success)
|
||||
Just False -> failure
|
||||
Nothing -> return ()
|
||||
return True
|
||||
}
|
||||
|
|
|
@ -88,11 +88,13 @@ module Mtlstats.Types (
|
|||
cpsNumber,
|
||||
cpsName,
|
||||
cpsPosition,
|
||||
cpsRookieFlag,
|
||||
cpsSuccessCallback,
|
||||
cpsFailureCallback,
|
||||
-- ** CreateGoalieState Lenses
|
||||
cgsNumber,
|
||||
cgsName,
|
||||
cgsRookieFlag,
|
||||
cgsSuccessCallback,
|
||||
cgsFailureCallback,
|
||||
-- ** EditPlayerState Lenses
|
||||
|
@ -328,6 +330,8 @@ data CreatePlayerState = CreatePlayerState
|
|||
-- ^ The player's name
|
||||
, _cpsPosition :: String
|
||||
-- ^ The player's position
|
||||
, _cpsRookieFlag :: Maybe Bool
|
||||
-- ^ Indicates whether or not the player is a rookie
|
||||
, _cpsSuccessCallback :: Action ()
|
||||
-- ^ The function to call on success
|
||||
, _cpsFailureCallback :: Action ()
|
||||
|
@ -336,10 +340,12 @@ data CreatePlayerState = CreatePlayerState
|
|||
|
||||
-- | Goalie creation status
|
||||
data CreateGoalieState = CreateGoalieState
|
||||
{ _cgsNumber :: Maybe Int
|
||||
{ _cgsNumber :: Maybe Int
|
||||
-- ^ The goalie's number
|
||||
, _cgsName :: String
|
||||
, _cgsName :: String
|
||||
-- ^ The goalie's name
|
||||
, _cgsRookieFlag :: Maybe Bool
|
||||
-- ^ Indicates whether or not the goalie is a rookie
|
||||
, _cgsSuccessCallback :: Action ()
|
||||
-- ^ The function to call on success
|
||||
, _cgsFailureCallback :: Action ()
|
||||
|
@ -807,6 +813,7 @@ newCreatePlayerState = CreatePlayerState
|
|||
{ _cpsNumber = Nothing
|
||||
, _cpsName = ""
|
||||
, _cpsPosition = ""
|
||||
, _cpsRookieFlag = Nothing
|
||||
, _cpsSuccessCallback = return ()
|
||||
, _cpsFailureCallback = return ()
|
||||
}
|
||||
|
@ -816,6 +823,7 @@ newCreateGoalieState :: CreateGoalieState
|
|||
newCreateGoalieState = CreateGoalieState
|
||||
{ _cgsNumber = Nothing
|
||||
, _cgsName = ""
|
||||
, _cgsRookieFlag = Nothing
|
||||
, _cgsSuccessCallback = return ()
|
||||
, _cgsFailureCallback = return ()
|
||||
}
|
||||
|
|
|
@ -312,51 +312,73 @@ editSelectedGoalieSpec = describe "editSelectedGoalie" $ mapM_
|
|||
goalie' n = newGoalie n "foo"
|
||||
|
||||
addPlayerSpec :: Spec
|
||||
addPlayerSpec = describe "addPlayer" $ do
|
||||
let
|
||||
p1 = newPlayer 1 "Joe" "centre"
|
||||
p2 = newPlayer 2 "Bob" "defense"
|
||||
db = newDatabase
|
||||
& dbPlayers .~ [p1]
|
||||
s pm = newProgState
|
||||
& progMode .~ pm
|
||||
& database .~ db
|
||||
addPlayerSpec = describe "addPlayer" $ mapM_
|
||||
(\(label, expectation, pm, players) -> context label $
|
||||
it expectation $ let
|
||||
ps = newProgState
|
||||
& progMode .~ pm
|
||||
& database.dbPlayers .~ [joe]
|
||||
ps' = addPlayer ps
|
||||
in ps'^.database.dbPlayers `shouldBe` players)
|
||||
|
||||
context "data available" $
|
||||
it "should create the player" $ let
|
||||
s' = addPlayer $ s $ CreatePlayer $ newCreatePlayerState
|
||||
& cpsNumber ?~ 2
|
||||
& cpsName .~ "Bob"
|
||||
& cpsPosition .~ "defense"
|
||||
in s'^.database.dbPlayers `shouldBe` [p1, p2]
|
||||
-- label, expectation, progMode, players
|
||||
[ ( "wrong mode", failure, MainMenu, [joe] )
|
||||
, ( "missing number", failure, noNum, [joe] )
|
||||
, ( "missing rookie flag", failure, noRookie, [joe] )
|
||||
, ( "rookie", success, mkRookie, [joe, rookie] )
|
||||
, ( "normal player", success, mkNormal, [joe, normal] )
|
||||
]
|
||||
|
||||
context "data unavailable" $
|
||||
it "should not create the player" $ let
|
||||
s' = addPlayer $ s MainMenu
|
||||
in s'^.database.dbPlayers `shouldBe` [p1]
|
||||
where
|
||||
failure = "should not create the player"
|
||||
success = "should create the player"
|
||||
noNum = mkpm Nothing (Just False)
|
||||
noRookie = mkpm (Just 3) Nothing
|
||||
mkRookie = mkpm (Just 3) (Just True)
|
||||
mkNormal = mkpm (Just 3) (Just False)
|
||||
joe = newPlayer 2 "Joe" "centre"
|
||||
rookie = bob True
|
||||
normal = bob False
|
||||
bob rf = newPlayer 3 "Bob" "defense" & pRookie .~ rf
|
||||
mkpm n rf = CreatePlayer $ newCreatePlayerState
|
||||
& cpsNumber .~ n
|
||||
& cpsName .~ "Bob"
|
||||
& cpsPosition .~ "defense"
|
||||
& cpsRookieFlag .~ rf
|
||||
|
||||
addGoalieSpec :: Spec
|
||||
addGoalieSpec = describe "addGoalie" $ do
|
||||
let
|
||||
g1 = newGoalie 2 "Joe"
|
||||
g2 = newGoalie 3 "Bob"
|
||||
db = newDatabase
|
||||
& dbGoalies .~ [g1]
|
||||
s pm = newProgState
|
||||
& database .~ db
|
||||
& progMode .~ pm
|
||||
addGoalieSpec = describe "addGoalie" $ mapM_
|
||||
(\(label, expectation, pm, goalies) -> context label $
|
||||
it expectation $ let
|
||||
ps = newProgState
|
||||
& progMode .~ pm
|
||||
& database.dbGoalies .~ [joe]
|
||||
ps' = addGoalie ps
|
||||
in ps'^.database.dbGoalies `shouldBe` goalies)
|
||||
|
||||
context "data available" $
|
||||
it "should create the goalie" $ let
|
||||
s' = addGoalie $ s $ CreateGoalie $ newCreateGoalieState
|
||||
& cgsNumber ?~ 3
|
||||
& cgsName .~ "Bob"
|
||||
in s'^.database.dbGoalies `shouldBe` [g1, g2]
|
||||
-- label, expectation, progMode, expected goalies
|
||||
[ ( "wrong mode", failure, MainMenu, [joe] )
|
||||
, ( "no number", failure, noNum, [joe] )
|
||||
, ( "no rookie flag", failure, noRookie, [joe] )
|
||||
, ( "rookie", success, mkRookie, [joe, rookie] )
|
||||
, ( "normal goalie", success, mkNormal, [joe, normal] )
|
||||
]
|
||||
|
||||
context "data unavailable" $
|
||||
it "should not create the goalie" $ let
|
||||
s' = addGoalie $ s MainMenu
|
||||
in s'^.database.dbGoalies `shouldBe` [g1]
|
||||
where
|
||||
failure = "should not create the goalie"
|
||||
success = "should create the goalie"
|
||||
noNum = cgs Nothing (Just False)
|
||||
noRookie = cgs (Just 3) Nothing
|
||||
mkRookie = cgs (Just 3) (Just True)
|
||||
mkNormal = cgs (Just 3) (Just False)
|
||||
joe = newGoalie 2 "Joe"
|
||||
rookie = bob True
|
||||
normal = bob False
|
||||
bob r = newGoalie 3 "Bob" & gRookie .~ r
|
||||
cgs n rf = CreateGoalie $ newCreateGoalieState
|
||||
& cgsNumber .~ n
|
||||
& cgsName .~ "Bob"
|
||||
& cgsRookieFlag .~ rf
|
||||
|
||||
resetCreatePlayerStateSpec :: Spec
|
||||
resetCreatePlayerStateSpec = describe "resetCreatePlayerState" $ let
|
||||
|
|
Loading…
Reference in New Issue
Block a user