commit
fc20259a48
|
@ -149,23 +149,19 @@ addPlayer s = fromMaybe s $ do
|
||||||
pos = cps^.cpsPosition
|
pos = cps^.cpsPosition
|
||||||
player = newPlayer num name pos
|
player = newPlayer num name pos
|
||||||
Just $ s & database.dbPlayers
|
Just $ s & database.dbPlayers
|
||||||
%~ (player:)
|
%~ (++[player])
|
||||||
|
|
||||||
-- | Awards the goal and assists to the players
|
-- | Awards the goal and assists to the players
|
||||||
recordGoalAssists :: ProgState -> ProgState
|
recordGoalAssists :: ProgState -> ProgState
|
||||||
recordGoalAssists ps = fromMaybe ps $ do
|
recordGoalAssists ps = fromMaybe ps $ do
|
||||||
let
|
let gs = ps^.progMode.gameStateL
|
||||||
gs = ps^.progMode.gameStateL
|
goalId <- gs^.goalBy
|
||||||
players = ps^.database.dbPlayers
|
let assistIds = gs^.assistsBy
|
||||||
(goalId, _) <- playerSearchExact (gs^.goalBy) players
|
|
||||||
assistIds <- mapM
|
|
||||||
(\name -> fst <$> playerSearchExact name players)
|
|
||||||
(gs^.assistsBy)
|
|
||||||
Just $ ps
|
Just $ ps
|
||||||
& awardGoal goalId
|
& awardGoal goalId
|
||||||
& (\s -> foldr awardAssist s assistIds)
|
& (\s -> foldr awardAssist s assistIds)
|
||||||
& progMode.gameStateL
|
& progMode.gameStateL
|
||||||
%~ (goalBy .~ "")
|
%~ (goalBy .~ Nothing)
|
||||||
. (assistsBy .~ [])
|
. (assistsBy .~ [])
|
||||||
. (pointsAccounted %~ succ)
|
. (pointsAccounted %~ succ)
|
||||||
|
|
||||||
|
|
|
@ -182,7 +182,8 @@ selectPlayerPrompt pStr callback = Prompt
|
||||||
& cpsName .~ sStr
|
& cpsName .~ sStr
|
||||||
& cpsSuccessCallback .~ do
|
& cpsSuccessCallback .~ do
|
||||||
modify $ progMode .~ mode
|
modify $ progMode .~ mode
|
||||||
callback (Just 0)
|
pIndex <- pred . length <$> gets (view $ database.dbPlayers)
|
||||||
|
callback $ Just pIndex
|
||||||
& cpsFailureCallback .~ do
|
& cpsFailureCallback .~ do
|
||||||
modify $ progMode .~ mode
|
modify $ progMode .~ mode
|
||||||
callback Nothing
|
callback Nothing
|
||||||
|
@ -210,12 +211,7 @@ recordGoalPrompt
|
||||||
recordGoalPrompt game goal = selectPlayerPrompt
|
recordGoalPrompt game goal = selectPlayerPrompt
|
||||||
( "*** GAME " ++ padNum 2 game ++ " ***\n"
|
( "*** GAME " ++ padNum 2 game ++ " ***\n"
|
||||||
++ "Who scored goal number " ++ show goal ++ "? "
|
++ "Who scored goal number " ++ show goal ++ "? "
|
||||||
) $ \case
|
) $ modify . (progMode.gameStateL.goalBy .~)
|
||||||
Nothing -> return ()
|
|
||||||
Just n -> nth n <$> gets (view $ database.dbPlayers)
|
|
||||||
>>= maybe
|
|
||||||
(return ())
|
|
||||||
(\p -> modify $ progMode.gameStateL.goalBy .~ p^.pName)
|
|
||||||
|
|
||||||
-- | Prompts for a player who assisted the goal
|
-- | Prompts for a player who assisted the goal
|
||||||
recordAssistPrompt
|
recordAssistPrompt
|
||||||
|
@ -232,14 +228,11 @@ recordAssistPrompt game goal assist = selectPlayerPrompt
|
||||||
++ "Assist #" ++ show assist ++ ": "
|
++ "Assist #" ++ show assist ++ ": "
|
||||||
) $ \case
|
) $ \case
|
||||||
Nothing -> modify recordGoalAssists
|
Nothing -> modify recordGoalAssists
|
||||||
Just n -> nth n <$> gets (view $ database.dbPlayers)
|
Just n -> do
|
||||||
>>= maybe
|
modify $ progMode.gameStateL.assistsBy %~ (++[n])
|
||||||
(return ())
|
nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy)
|
||||||
(\p -> do
|
when (nAssists >= maxAssists) $
|
||||||
modify $ progMode.gameStateL.assistsBy %~ (++[p^.pName])
|
modify recordGoalAssists
|
||||||
nAssists <- length <$> gets (view $ progMode.gameStateL.assistsBy)
|
|
||||||
when (nAssists >= maxAssists) $
|
|
||||||
modify recordGoalAssists)
|
|
||||||
|
|
||||||
drawSimplePrompt :: String -> ProgState -> C.Update ()
|
drawSimplePrompt :: String -> ProgState -> C.Update ()
|
||||||
drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer
|
drawSimplePrompt pStr s = C.drawString $ pStr ++ s^.inputBuffer
|
||||||
|
|
|
@ -207,10 +207,12 @@ data GameState = GameState
|
||||||
-- ^ Set to 'True' when the user confirms the entered data
|
-- ^ Set to 'True' when the user confirms the entered data
|
||||||
, _pointsAccounted :: Int
|
, _pointsAccounted :: Int
|
||||||
-- ^ The number of game points accounted for
|
-- ^ The number of game points accounted for
|
||||||
, _goalBy :: String
|
, _goalBy :: Maybe Int
|
||||||
-- ^ The player who scored the most recently entered goal
|
-- ^ The index number of the player who scored the most recently
|
||||||
, _assistsBy :: [String]
|
-- entered goal
|
||||||
-- ^ The players who have assisted the most recently entered goal
|
, _assistsBy :: [Int]
|
||||||
|
-- ^ The index numbers of the players who have assisted the most
|
||||||
|
-- recently entered goal
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
-- | The type of game
|
-- | The type of game
|
||||||
|
@ -507,7 +509,7 @@ newGameState = GameState
|
||||||
, _overtimeFlag = Nothing
|
, _overtimeFlag = Nothing
|
||||||
, _dataVerified = False
|
, _dataVerified = False
|
||||||
, _pointsAccounted = 0
|
, _pointsAccounted = 0
|
||||||
, _goalBy = ""
|
, _goalBy = Nothing
|
||||||
, _assistsBy = []
|
, _assistsBy = []
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
|
@ -342,7 +342,7 @@ addPlayerSpec = describe "addPlayer" $ do
|
||||||
p1 = newPlayer 1 "Joe" "centre"
|
p1 = newPlayer 1 "Joe" "centre"
|
||||||
p2 = newPlayer 2 "Bob" "defense"
|
p2 = newPlayer 2 "Bob" "defense"
|
||||||
db = newDatabase
|
db = newDatabase
|
||||||
& dbPlayers .~ [p2]
|
& dbPlayers .~ [p1]
|
||||||
s pm = newProgState
|
s pm = newProgState
|
||||||
& progMode .~ pm
|
& progMode .~ pm
|
||||||
& database .~ db
|
& database .~ db
|
||||||
|
@ -350,15 +350,15 @@ addPlayerSpec = describe "addPlayer" $ do
|
||||||
context "data available" $
|
context "data available" $
|
||||||
it "should create the player" $ let
|
it "should create the player" $ let
|
||||||
s' = addPlayer $ s $ CreatePlayer $ newCreatePlayerState
|
s' = addPlayer $ s $ CreatePlayer $ newCreatePlayerState
|
||||||
& cpsNumber ?~ 1
|
& cpsNumber ?~ 2
|
||||||
& cpsName .~ "Joe"
|
& cpsName .~ "Bob"
|
||||||
& cpsPosition .~ "centre"
|
& cpsPosition .~ "defense"
|
||||||
in s'^.database.dbPlayers `shouldBe` [p1, p2]
|
in s'^.database.dbPlayers `shouldBe` [p1, p2]
|
||||||
|
|
||||||
context "data unavailable" $
|
context "data unavailable" $
|
||||||
it "should not create the player" $ let
|
it "should not create the player" $ let
|
||||||
s' = addPlayer $ s MainMenu
|
s' = addPlayer $ s MainMenu
|
||||||
in s'^.database.dbPlayers `shouldBe` [p2]
|
in s'^.database.dbPlayers `shouldBe` [p1]
|
||||||
|
|
||||||
recordGoalAssistsSpec :: Spec
|
recordGoalAssistsSpec :: Spec
|
||||||
recordGoalAssistsSpec = describe "recordGoalAssists" $ do
|
recordGoalAssistsSpec = describe "recordGoalAssists" $ do
|
||||||
|
@ -371,8 +371,8 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do
|
||||||
= newProgState
|
= newProgState
|
||||||
& database.dbPlayers .~ [joe, bob, steve, dave]
|
& database.dbPlayers .~ [joe, bob, steve, dave]
|
||||||
& progMode.gameStateL
|
& progMode.gameStateL
|
||||||
%~ (goalBy .~ "Joe")
|
%~ (goalBy ?~ 0)
|
||||||
. (assistsBy .~ ["Bob", "Steve"])
|
. (assistsBy .~ [1, 2])
|
||||||
& recordGoalAssists
|
& recordGoalAssists
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
|
@ -399,7 +399,7 @@ recordGoalAssistsSpec = describe "recordGoalAssists" $ do
|
||||||
]
|
]
|
||||||
|
|
||||||
it "should clear the goalBy value" $
|
it "should clear the goalBy value" $
|
||||||
ps^.progMode.gameStateL.goalBy `shouldBe` ""
|
ps^.progMode.gameStateL.goalBy `shouldBe` Nothing
|
||||||
|
|
||||||
it "should clear the assistsBy list" $
|
it "should clear the assistsBy list" $
|
||||||
ps^.progMode.gameStateL.assistsBy `shouldBe` []
|
ps^.progMode.gameStateL.assistsBy `shouldBe` []
|
||||||
|
|
Loading…
Reference in New Issue
Block a user