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