implemented overtimeCheck
This commit is contained in:
parent
7ee53ee8c1
commit
3c8302174b
|
@ -27,9 +27,10 @@ module Mtlstats.Actions
|
||||||
, startNewGame
|
, startNewGame
|
||||||
, addChar
|
, addChar
|
||||||
, removeChar
|
, removeChar
|
||||||
|
, overtimeCheck
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Lens.Micro (over, (&), (.~), (?~), (%~))
|
import Lens.Micro (over, (^.), (&), (.~), (?~), (%~))
|
||||||
|
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
|
|
||||||
|
@ -58,3 +59,14 @@ removeChar :: ProgState -> ProgState
|
||||||
removeChar = inputBuffer %~ \case
|
removeChar = inputBuffer %~ \case
|
||||||
"" -> ""
|
"" -> ""
|
||||||
str -> init str
|
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
|
||||||
|
|
|
@ -53,5 +53,6 @@ handleEvent e = gets (view progMode) >>= \case
|
||||||
return True
|
return True
|
||||||
| null $ gs ^. awayScore -> do
|
| null $ gs ^. awayScore -> do
|
||||||
promptHandler awayScorePrompt e
|
promptHandler awayScorePrompt e
|
||||||
|
modify overtimeCheck
|
||||||
return True
|
return True
|
||||||
| otherwise -> undefined
|
| otherwise -> undefined
|
||||||
|
|
|
@ -47,6 +47,7 @@ module Mtlstats.Types (
|
||||||
otherTeam,
|
otherTeam,
|
||||||
homeScore,
|
homeScore,
|
||||||
awayScore,
|
awayScore,
|
||||||
|
overtimeFlag,
|
||||||
-- ** Database Lenses
|
-- ** Database Lenses
|
||||||
dbPlayers,
|
dbPlayers,
|
||||||
dbGoalies,
|
dbGoalies,
|
||||||
|
@ -139,6 +140,8 @@ data GameState = GameState
|
||||||
-- ^ The home team's score
|
-- ^ The home team's score
|
||||||
, _awayScore :: Maybe Int
|
, _awayScore :: Maybe Int
|
||||||
-- ^ The away team's score
|
-- ^ The away team's score
|
||||||
|
, _overtimeFlag :: Maybe Bool
|
||||||
|
-- ^ Indicates whether or not the game went into overtime
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
-- | The program mode
|
-- | The program mode
|
||||||
|
@ -404,6 +407,7 @@ newGameState = GameState
|
||||||
, _otherTeam = ""
|
, _otherTeam = ""
|
||||||
, _homeScore = Nothing
|
, _homeScore = Nothing
|
||||||
, _awayScore = Nothing
|
, _awayScore = Nothing
|
||||||
|
, _overtimeFlag = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Constructor for a 'Database'
|
-- | Constructor for a 'Database'
|
||||||
|
|
|
@ -22,7 +22,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
module ActionsSpec (spec) where
|
module ActionsSpec (spec) where
|
||||||
|
|
||||||
import Control.Monad (replicateM)
|
import Control.Monad (replicateM)
|
||||||
import Lens.Micro ((&), (.~), (?~), (^.))
|
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
|
||||||
import System.Random (randomRIO)
|
import System.Random (randomRIO)
|
||||||
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldNotBe)
|
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldNotBe)
|
||||||
|
|
||||||
|
@ -36,6 +36,7 @@ spec = describe "Mtlstats.Actions" $ do
|
||||||
resetYtdSpec
|
resetYtdSpec
|
||||||
addCharSpec
|
addCharSpec
|
||||||
removeCharSpec
|
removeCharSpec
|
||||||
|
overtimeCheckSpec
|
||||||
|
|
||||||
startNewSeasonSpec :: Spec
|
startNewSeasonSpec :: Spec
|
||||||
startNewSeasonSpec = describe "startNewSeason" $ do
|
startNewSeasonSpec = describe "startNewSeason" $ do
|
||||||
|
@ -126,6 +127,62 @@ removeCharSpec = describe "removeChar" $ do
|
||||||
& removeChar
|
& removeChar
|
||||||
in s ^. inputBuffer `shouldBe` "fo"
|
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 :: IO Player
|
||||||
makePlayer = Player
|
makePlayer = Player
|
||||||
<$> makeNum
|
<$> makeNum
|
||||||
|
|
Loading…
Reference in New Issue
Block a user