implemented overtimeCheck

This commit is contained in:
Jonathan Lamothe 2019-08-29 00:12:30 -04:00
parent 7ee53ee8c1
commit 3c8302174b
4 changed files with 84 additions and 10 deletions

View File

@ -27,9 +27,10 @@ module Mtlstats.Actions
, startNewGame
, addChar
, removeChar
, overtimeCheck
) where
import Lens.Micro (over, (&), (.~), (?~), (%~))
import Lens.Micro (over, (^.), (&), (.~), (?~), (%~))
import Mtlstats.Types
@ -58,3 +59,14 @@ removeChar :: ProgState -> ProgState
removeChar = inputBuffer %~ \case
"" -> ""
str -> init str
-- | Determines whether or not to perform a check for overtime
overtimeCheck :: ProgState -> ProgState
overtimeCheck s
| gameTied (s^.progMode.gameStateL) =
s & progMode.gameStateL
%~ (homeScore .~ Nothing)
. (awayScore .~ Nothing)
| gameWon (s^.progMode.gameStateL) =
s & progMode.gameStateL.overtimeFlag ?~ False
| otherwise = s

View File

@ -53,5 +53,6 @@ handleEvent e = gets (view progMode) >>= \case
return True
| null $ gs ^. awayScore -> do
promptHandler awayScorePrompt e
modify overtimeCheck
return True
| otherwise -> undefined

View File

@ -47,6 +47,7 @@ module Mtlstats.Types (
otherTeam,
homeScore,
awayScore,
overtimeFlag,
-- ** Database Lenses
dbPlayers,
dbGoalies,
@ -131,14 +132,16 @@ data ProgState = ProgState
-- | The game state
data GameState = GameState
{ _gameType :: Maybe GameType
{ _gameType :: Maybe GameType
-- ^ The type of game (home/away)
, _otherTeam :: String
, _otherTeam :: String
-- ^ The name of the other team
, _homeScore :: Maybe Int
, _homeScore :: Maybe Int
-- ^ The home team's score
, _awayScore :: Maybe Int
, _awayScore :: Maybe Int
-- ^ The away team's score
, _overtimeFlag :: Maybe Bool
-- ^ Indicates whether or not the game went into overtime
} deriving (Eq, Show)
-- | The program mode
@ -400,10 +403,11 @@ newProgState = ProgState
-- | Constructor for a 'GameState'
newGameState :: GameState
newGameState = GameState
{ _gameType = Nothing
, _otherTeam = ""
, _homeScore = Nothing
, _awayScore = Nothing
{ _gameType = Nothing
, _otherTeam = ""
, _homeScore = Nothing
, _awayScore = Nothing
, _overtimeFlag = Nothing
}
-- | Constructor for a 'Database'

View File

@ -22,7 +22,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module ActionsSpec (spec) where
import Control.Monad (replicateM)
import Lens.Micro ((&), (.~), (?~), (^.))
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
import System.Random (randomRIO)
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldNotBe)
@ -36,6 +36,7 @@ spec = describe "Mtlstats.Actions" $ do
resetYtdSpec
addCharSpec
removeCharSpec
overtimeCheckSpec
startNewSeasonSpec :: Spec
startNewSeasonSpec = describe "startNewSeason" $ do
@ -126,6 +127,62 @@ removeCharSpec = describe "removeChar" $ do
& removeChar
in s ^. inputBuffer `shouldBe` "fo"
overtimeCheckSpec = describe "overtimeCheck" $ do
context "tie game" $ do
let
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 1)
. (awayScore ?~ 1)
& overtimeCheck
it "should clear the home score" $
s^.progMode.gameStateL.homeScore `shouldBe` Nothing
it "should clear the away score" $
s^.progMode.gameStateL.awayScore `shouldBe` Nothing
it "should leave the overtimeFlag blank" $
s^.progMode.gameStateL.overtimeFlag `shouldBe` Nothing
context "game won" $ do
let
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 2)
. (awayScore ?~ 1)
& overtimeCheck
it "should not change the home score" $
s^.progMode.gameStateL.homeScore `shouldBe` Just 2
it "should not change the away score" $
s^.progMode.gameStateL.awayScore `shouldBe` Just 1
it "should set the overtimeCheck flag to False" $
s^.progMode.gameStateL.overtimeFlag `shouldBe` Just False
context "game lost" $ do
let
s = newProgState
& progMode.gameStateL
%~ (gameType ?~ HomeGame)
. (homeScore ?~ 1)
. (awayScore ?~ 2)
& overtimeCheck
it "should not change the home score" $
s^.progMode.gameStateL.homeScore `shouldBe` Just 1
it "should not change the away score" $
s^.progMode.gameStateL.awayScore `shouldBe` Just 2
it "should leave the overtimeCheck flag blank" $
s^.progMode.gameStateL.overtimeFlag `shouldBe` Nothing
makePlayer :: IO Player
makePlayer = Player
<$> makeNum