2019-08-20 11:31:03 -04:00
|
|
|
{-
|
|
|
|
|
|
|
|
mtlstats
|
2020-01-11 00:29:45 -05:00
|
|
|
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
2019-08-20 11:31:03 -04:00
|
|
|
<rheal.lamothe@gmail.com>
|
|
|
|
|
|
|
|
This program is free software: you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation, either version 3 of the License, or (at
|
|
|
|
your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful, but
|
|
|
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
|
|
|
General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2019-10-11 23:13:00 -04:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
|
2019-08-20 11:31:03 -04:00
|
|
|
module ActionsSpec (spec) where
|
|
|
|
|
2019-08-21 15:57:52 -04:00
|
|
|
import Control.Monad (replicateM)
|
2020-01-11 02:29:17 -05:00
|
|
|
import Lens.Micro ((^.), (&), (.~), (?~), (%~))
|
2019-10-11 23:13:00 -04:00
|
|
|
import Test.Hspec
|
|
|
|
( Spec
|
|
|
|
, context
|
|
|
|
, describe
|
|
|
|
, it
|
|
|
|
, shouldBe
|
|
|
|
, shouldNotBe
|
|
|
|
, shouldSatisfy
|
|
|
|
)
|
2019-08-20 12:26:24 -04:00
|
|
|
|
|
|
|
import Mtlstats.Actions
|
|
|
|
import Mtlstats.Types
|
2019-08-20 11:31:03 -04:00
|
|
|
|
2019-11-07 22:36:08 -05:00
|
|
|
import qualified Actions.NewGameSpec as NewGame
|
2019-10-25 01:44:56 -04:00
|
|
|
import qualified TypesSpec as TS
|
|
|
|
|
2019-08-20 11:31:03 -04:00
|
|
|
spec :: Spec
|
|
|
|
spec = describe "Mtlstats.Actions" $ do
|
2019-08-20 12:26:24 -04:00
|
|
|
startNewSeasonSpec
|
|
|
|
startNewGameSpec
|
2019-08-21 15:57:52 -04:00
|
|
|
resetYtdSpec
|
2020-01-11 02:29:17 -05:00
|
|
|
clearRookiesSpec
|
2019-11-14 11:21:52 -05:00
|
|
|
resetStandingsSpec
|
2019-08-24 17:01:18 -04:00
|
|
|
addCharSpec
|
|
|
|
removeCharSpec
|
2019-09-09 10:51:32 -04:00
|
|
|
createPlayerSpec
|
2019-10-25 00:37:14 -04:00
|
|
|
createGoalieSpec
|
2019-12-17 12:16:26 -05:00
|
|
|
editSpec
|
2019-11-01 04:00:29 -04:00
|
|
|
editPlayerSpec
|
2020-01-09 01:01:51 -05:00
|
|
|
editSelectedPlayerSpec
|
2019-11-12 23:48:31 -05:00
|
|
|
editGoalieSpec
|
2020-01-09 01:31:24 -05:00
|
|
|
editSelectedGoalieSpec
|
2020-01-15 00:26:46 -05:00
|
|
|
editStandingsSpec
|
2019-09-09 23:35:28 -04:00
|
|
|
addPlayerSpec
|
2019-10-26 02:05:55 -04:00
|
|
|
addGoalieSpec
|
2019-10-25 01:44:56 -04:00
|
|
|
resetCreatePlayerStateSpec
|
|
|
|
resetCreateGoalieStateSpec
|
2019-10-11 23:13:00 -04:00
|
|
|
backHomeSpec
|
2019-10-15 00:16:44 -04:00
|
|
|
scrollUpSpec
|
|
|
|
scrollDownSpec
|
2019-11-07 22:36:08 -05:00
|
|
|
NewGame.spec
|
2019-08-20 12:26:24 -04:00
|
|
|
|
|
|
|
startNewSeasonSpec :: Spec
|
|
|
|
startNewSeasonSpec = describe "startNewSeason" $ do
|
|
|
|
let
|
|
|
|
s = newProgState
|
|
|
|
& database . dbGames .~ 1
|
|
|
|
& startNewSeason
|
|
|
|
|
|
|
|
it "should set the progState to NewSeason" $
|
2019-09-13 02:26:03 -04:00
|
|
|
show (s^.progMode) `shouldBe` "NewSeason"
|
2019-08-20 11:31:03 -04:00
|
|
|
|
2019-08-20 12:26:24 -04:00
|
|
|
it "should set the number of games to 0" $
|
|
|
|
s ^. database . dbGames `shouldBe` 0
|
2019-08-20 11:31:03 -04:00
|
|
|
|
2019-08-20 12:26:24 -04:00
|
|
|
startNewGameSpec :: Spec
|
2019-08-22 01:18:02 -04:00
|
|
|
startNewGameSpec = describe "startNewGame" $ do
|
2019-08-23 09:32:21 -04:00
|
|
|
let s = startNewGame newProgState
|
2019-08-22 01:18:02 -04:00
|
|
|
|
2019-08-23 09:32:21 -04:00
|
|
|
it "should increment the number of games" $
|
|
|
|
s ^. database . dbGames `shouldBe` 1
|
2019-08-22 01:18:02 -04:00
|
|
|
|
|
|
|
it "should set the mode to NewGame" $
|
2019-09-13 02:26:03 -04:00
|
|
|
show (s^.progMode) `shouldBe` "NewGame"
|
2019-08-21 15:57:52 -04:00
|
|
|
|
|
|
|
resetYtdSpec :: Spec
|
|
|
|
resetYtdSpec = describe "resetYtd" $
|
|
|
|
it "should reset the year-to-date stats for all players" $ do
|
2019-11-07 22:36:08 -05:00
|
|
|
ps <- replicateM 2 TS.makePlayer
|
|
|
|
gs <- replicateM 2 TS.makeGoalie
|
2019-08-21 15:57:52 -04:00
|
|
|
let
|
|
|
|
s = newProgState
|
|
|
|
& database . dbPlayers .~ ps
|
|
|
|
& database . dbGoalies .~ gs
|
|
|
|
& resetYtd
|
|
|
|
mapM_
|
|
|
|
(\p -> do
|
|
|
|
let
|
|
|
|
ytd = p ^. pYtd
|
|
|
|
lt = p ^. pLifetime
|
|
|
|
ytd ^. psGoals `shouldBe` 0
|
|
|
|
ytd ^. psAssists `shouldBe` 0
|
|
|
|
ytd ^. psPMin `shouldBe` 0
|
|
|
|
lt ^. psGoals `shouldNotBe` 0
|
|
|
|
lt ^. psAssists `shouldNotBe` 0
|
|
|
|
lt ^. psPMin `shouldNotBe` 0) $
|
|
|
|
s ^. database . dbPlayers
|
|
|
|
mapM_
|
|
|
|
(\g -> do
|
|
|
|
let
|
|
|
|
ytd = g ^. gYtd
|
|
|
|
lt = g ^. gLifetime
|
|
|
|
ytd ^. gsGames `shouldBe` 0
|
|
|
|
ytd ^. gsMinsPlayed `shouldBe` 0
|
|
|
|
ytd ^. gsGoalsAllowed `shouldBe` 0
|
|
|
|
ytd ^. gsWins `shouldBe` 0
|
|
|
|
ytd ^. gsLosses `shouldBe` 0
|
|
|
|
ytd ^. gsTies `shouldBe` 0
|
|
|
|
lt ^. gsGames `shouldNotBe` 0
|
|
|
|
lt ^. gsMinsPlayed `shouldNotBe` 0
|
|
|
|
lt ^. gsGoalsAllowed `shouldNotBe` 0
|
|
|
|
lt ^. gsWins `shouldNotBe` 0
|
|
|
|
lt ^. gsLosses `shouldNotBe` 0
|
|
|
|
lt ^. gsTies `shouldNotBe` 0) $
|
|
|
|
s ^. database . dbGoalies
|
|
|
|
|
2020-01-11 02:29:17 -05:00
|
|
|
clearRookiesSpec :: Spec
|
|
|
|
clearRookiesSpec = describe "clearRookies" $ do
|
|
|
|
let
|
|
|
|
|
|
|
|
players =
|
|
|
|
[ newPlayer 1 "Joe" "centre" & pRookie .~ True
|
|
|
|
, newPlayer 2 "Bob" "centre" & pRookie .~ False
|
|
|
|
]
|
|
|
|
|
|
|
|
goalies =
|
|
|
|
[ newGoalie 3 "Bill" & gRookie .~ True
|
|
|
|
, newGoalie 4 "Doug" & gRookie .~ False
|
|
|
|
]
|
|
|
|
|
|
|
|
ps = newProgState
|
|
|
|
& database
|
|
|
|
%~ (dbPlayers .~ players)
|
|
|
|
. (dbGoalies .~ goalies)
|
|
|
|
|
|
|
|
ps' = clearRookies ps
|
|
|
|
|
|
|
|
context "Players" $ mapM_
|
|
|
|
(\p -> let
|
|
|
|
name = p^.pName
|
|
|
|
rFlag = p^.pRookie
|
|
|
|
in context name $
|
|
|
|
it "should not be a rookie" $
|
|
|
|
rFlag `shouldBe` False)
|
|
|
|
(ps'^.database.dbPlayers)
|
|
|
|
|
|
|
|
context "Goalies" $ mapM_
|
|
|
|
(\g -> let
|
|
|
|
name = g^.gName
|
|
|
|
rFlag = g^.gRookie
|
|
|
|
in context name $
|
|
|
|
it "should not be a rookie" $
|
|
|
|
rFlag `shouldBe` False)
|
|
|
|
(ps'^.database.dbGoalies)
|
|
|
|
|
2019-11-14 11:21:52 -05:00
|
|
|
resetStandingsSpec :: Spec
|
|
|
|
resetStandingsSpec = describe "resetStandings" $ do
|
|
|
|
let
|
|
|
|
home = GameStats
|
|
|
|
{ _gmsWins = 1
|
|
|
|
, _gmsLosses = 2
|
|
|
|
, _gmsOvertime = 3
|
|
|
|
, _gmsGoalsFor = 4
|
|
|
|
, _gmsGoalsAgainst = 5
|
|
|
|
}
|
|
|
|
|
|
|
|
away = GameStats
|
|
|
|
{ _gmsWins = 6
|
|
|
|
, _gmsLosses = 7
|
|
|
|
, _gmsOvertime = 8
|
|
|
|
, _gmsGoalsFor = 9
|
|
|
|
, _gmsGoalsAgainst = 10
|
|
|
|
}
|
|
|
|
|
|
|
|
db = newDatabase
|
|
|
|
& dbHomeGameStats .~ home
|
|
|
|
& dbAwayGameStats .~ away
|
|
|
|
|
|
|
|
ps = newProgState
|
|
|
|
& database .~ db
|
|
|
|
& resetStandings
|
|
|
|
|
|
|
|
context "home standings" $
|
|
|
|
it "should be reset" $
|
|
|
|
ps^.database.dbHomeGameStats `shouldBe` newGameStats
|
|
|
|
|
|
|
|
context "away standings" $
|
|
|
|
it "should be reset" $
|
|
|
|
ps^.database.dbAwayGameStats `shouldBe` newGameStats
|
|
|
|
|
2019-08-24 17:01:18 -04:00
|
|
|
addCharSpec :: Spec
|
|
|
|
addCharSpec = describe "addChar" $
|
|
|
|
it "should add the character to the input buffer" $ let
|
|
|
|
s = newProgState
|
|
|
|
& inputBuffer .~ "foo"
|
|
|
|
& addChar 'd'
|
|
|
|
in s ^. inputBuffer `shouldBe` "food"
|
|
|
|
|
|
|
|
removeCharSpec :: Spec
|
|
|
|
removeCharSpec = describe "removeChar" $ do
|
|
|
|
|
|
|
|
context "empty" $
|
|
|
|
it "should remove the character from the input buffer" $ let
|
|
|
|
s = removeChar newProgState
|
|
|
|
in s ^. inputBuffer `shouldBe` ""
|
|
|
|
|
|
|
|
context "not empty" $
|
|
|
|
it "should remove the character from the input buffer" $ let
|
|
|
|
s = newProgState
|
|
|
|
& inputBuffer .~ "foo"
|
|
|
|
& removeChar
|
|
|
|
in s ^. inputBuffer `shouldBe` "fo"
|
|
|
|
|
2019-09-09 10:51:32 -04:00
|
|
|
createPlayerSpec :: Spec
|
|
|
|
createPlayerSpec = describe "createPlayer" $
|
|
|
|
it "should change the mode appropriately" $ let
|
|
|
|
s = createPlayer newProgState
|
2019-09-13 02:26:03 -04:00
|
|
|
in show (s^.progMode) `shouldBe` "CreatePlayer"
|
2019-09-09 10:51:32 -04:00
|
|
|
|
2019-10-25 00:37:14 -04:00
|
|
|
createGoalieSpec :: Spec
|
|
|
|
createGoalieSpec = describe "createGoalie" $
|
|
|
|
it "should change the mode appropriately" $ let
|
|
|
|
s = createGoalie newProgState
|
|
|
|
in show (s^.progMode) `shouldBe` "CreateGoalie"
|
|
|
|
|
2019-12-17 12:16:26 -05:00
|
|
|
editSpec :: Spec
|
|
|
|
editSpec = describe "edit" $
|
|
|
|
it "should change the mode to EditMenu" $ let
|
|
|
|
ps = edit newProgState
|
|
|
|
in show (ps^.progMode) `shouldBe` "EditMenu"
|
|
|
|
|
2019-11-01 04:00:29 -04:00
|
|
|
editPlayerSpec :: Spec
|
|
|
|
editPlayerSpec = describe "editPlayer" $
|
|
|
|
it "should change the mode appropriately" $ let
|
|
|
|
s = editPlayer newProgState
|
|
|
|
in show (s^.progMode) `shouldBe` "EditPlayer"
|
|
|
|
|
2020-01-09 01:01:51 -05:00
|
|
|
editSelectedPlayerSpec :: Spec
|
|
|
|
editSelectedPlayerSpec = describe "editSelectedPlayer" $ mapM_
|
|
|
|
(\(label, pState, expected) -> context label $
|
|
|
|
it "should edit the players appropriately" $ let
|
|
|
|
pState' = editSelectedPlayer (pName .~ "foo") pState
|
|
|
|
players' = pState'^.database.dbPlayers
|
|
|
|
in players' `shouldBe` expected)
|
|
|
|
|
|
|
|
-- label, initial state, expected
|
|
|
|
[ ( "wrong mode", baseState, players )
|
|
|
|
, ( "not selected", changePlayer Nothing, players )
|
|
|
|
, ( "player 0", changePlayer $ Just 0, changed0 )
|
|
|
|
, ( "player 1", changePlayer $ Just 1, changed1 )
|
|
|
|
, ( "out of bounds", changePlayer $ Just 2, players )
|
|
|
|
]
|
|
|
|
|
|
|
|
where
|
|
|
|
baseState = newProgState & database.dbPlayers .~ players
|
|
|
|
changePlayer n = baseState
|
|
|
|
& (progMode.editPlayerStateL.epsSelectedPlayer .~ n)
|
|
|
|
players = [ player 0, player 1 ]
|
|
|
|
changed0 = [ player' 0, player 1 ]
|
|
|
|
changed1 = [ player 0, player' 1 ]
|
|
|
|
player n = newPlayer n ("Player " ++ show n) "pos"
|
|
|
|
player' n = newPlayer n "foo" "pos"
|
|
|
|
|
2019-11-12 23:48:31 -05:00
|
|
|
editGoalieSpec :: Spec
|
|
|
|
editGoalieSpec = describe "editGoalie" $
|
|
|
|
it "should change the mode appropriately" $ let
|
|
|
|
s = editGoalie newProgState
|
|
|
|
in show (s^.progMode) `shouldBe` "EditGoalie"
|
|
|
|
|
2020-01-09 01:31:24 -05:00
|
|
|
editSelectedGoalieSpec :: Spec
|
|
|
|
editSelectedGoalieSpec = describe "editSelectedGoalie" $ mapM_
|
|
|
|
(\(label, pState, expected) -> context label $
|
|
|
|
it "should edit the goalies appropriately" $ let
|
|
|
|
pState' = editSelectedGoalie (gName .~ "foo") pState
|
|
|
|
goalies' = pState'^.database.dbGoalies
|
|
|
|
in goalies' `shouldBe` expected)
|
|
|
|
|
|
|
|
-- label, initial state, expected
|
|
|
|
[ ( "wrong mode", baseState, goalies )
|
|
|
|
, ( "not selected", changeGoalie Nothing, goalies )
|
2020-01-09 01:43:35 -05:00
|
|
|
, ( "goalie 0", changeGoalie $ Just 0, changed0 )
|
|
|
|
, ( "goalie 1", changeGoalie $ Just 1, changed1 )
|
2020-01-09 01:31:24 -05:00
|
|
|
, ( "out of bounds", changeGoalie $ Just 2, goalies )
|
|
|
|
]
|
|
|
|
|
|
|
|
where
|
|
|
|
baseState = newProgState & database.dbGoalies .~ goalies
|
|
|
|
changeGoalie n = baseState
|
|
|
|
& (progMode.editGoalieStateL.egsSelectedGoalie .~ n)
|
|
|
|
goalies = [ goalie 0, goalie 1 ]
|
|
|
|
changed0 = [ goalie' 0, goalie 1 ]
|
|
|
|
changed1 = [ goalie 0, goalie' 1 ]
|
|
|
|
goalie n = newGoalie n ("Player " ++ show n)
|
|
|
|
goalie' n = newGoalie n "foo"
|
|
|
|
|
2020-01-15 00:26:46 -05:00
|
|
|
editStandingsSpec :: Spec
|
|
|
|
editStandingsSpec = describe "editStandings" $ let
|
|
|
|
ps = newProgState
|
|
|
|
ps' = editStandings ps
|
|
|
|
in it "should set progMode to EditStandings" $
|
|
|
|
ps'^.progMode `shouldSatisfy` \case
|
|
|
|
EditStandings -> True
|
|
|
|
_ -> False
|
|
|
|
|
2019-09-09 23:35:28 -04:00
|
|
|
addPlayerSpec :: Spec
|
|
|
|
addPlayerSpec = describe "addPlayer" $ do
|
|
|
|
let
|
|
|
|
p1 = newPlayer 1 "Joe" "centre"
|
|
|
|
p2 = newPlayer 2 "Bob" "defense"
|
|
|
|
db = newDatabase
|
2019-09-28 01:46:28 -04:00
|
|
|
& dbPlayers .~ [p1]
|
2019-09-09 23:35:28 -04:00
|
|
|
s pm = newProgState
|
|
|
|
& progMode .~ pm
|
|
|
|
& database .~ db
|
|
|
|
|
|
|
|
context "data available" $
|
|
|
|
it "should create the player" $ let
|
|
|
|
s' = addPlayer $ s $ CreatePlayer $ newCreatePlayerState
|
2019-09-28 01:46:28 -04:00
|
|
|
& cpsNumber ?~ 2
|
|
|
|
& cpsName .~ "Bob"
|
|
|
|
& cpsPosition .~ "defense"
|
2019-09-09 23:35:28 -04:00
|
|
|
in s'^.database.dbPlayers `shouldBe` [p1, p2]
|
|
|
|
|
|
|
|
context "data unavailable" $
|
|
|
|
it "should not create the player" $ let
|
|
|
|
s' = addPlayer $ s MainMenu
|
2019-09-28 01:46:28 -04:00
|
|
|
in s'^.database.dbPlayers `shouldBe` [p1]
|
2019-09-09 23:35:28 -04:00
|
|
|
|
2019-10-26 02:05:55 -04:00
|
|
|
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
|
|
|
|
|
|
|
|
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]
|
|
|
|
|
|
|
|
context "data unavailable" $
|
|
|
|
it "should not create the goalie" $ let
|
|
|
|
s' = addGoalie $ s MainMenu
|
|
|
|
in s'^.database.dbGoalies `shouldBe` [g1]
|
|
|
|
|
2019-10-25 01:44:56 -04:00
|
|
|
resetCreatePlayerStateSpec :: Spec
|
|
|
|
resetCreatePlayerStateSpec = describe "resetCreatePlayerState" $ let
|
|
|
|
cps = newCreatePlayerState
|
|
|
|
& cpsNumber ?~ 1
|
|
|
|
& cpsName .~ "Joe"
|
|
|
|
& cpsPosition .~ "centre"
|
|
|
|
ps = resetCreatePlayerState $
|
|
|
|
newProgState & progMode.createPlayerStateL .~ cps
|
|
|
|
in TS.compareTest (ps^.progMode.createPlayerStateL) newCreatePlayerState
|
|
|
|
|
|
|
|
resetCreateGoalieStateSpec :: Spec
|
|
|
|
resetCreateGoalieStateSpec = describe "resetCreateGoalieState" $ let
|
|
|
|
cgs = newCreateGoalieState
|
|
|
|
& cgsNumber ?~ 1
|
|
|
|
& cgsName .~ "Joe"
|
|
|
|
ps = resetCreateGoalieState $
|
|
|
|
newProgState & progMode.createGoalieStateL .~ cgs
|
|
|
|
in TS.compareTest (ps^.progMode.createGoalieStateL) newCreateGoalieState
|
|
|
|
|
2019-10-11 23:13:00 -04:00
|
|
|
backHomeSpec :: Spec
|
|
|
|
backHomeSpec = describe "backHome" $ do
|
|
|
|
let
|
|
|
|
input = newProgState
|
|
|
|
& progMode.gameStateL .~ newGameState
|
|
|
|
& inputBuffer .~ "foo"
|
|
|
|
& scrollOffset .~ 123
|
|
|
|
result = backHome input
|
|
|
|
|
|
|
|
it "should set the program mode back to MainMenu" $
|
|
|
|
result^.progMode `shouldSatisfy` \case
|
|
|
|
MainMenu -> True
|
|
|
|
_ -> False
|
|
|
|
|
|
|
|
it "should clear the input buffer" $
|
|
|
|
result^.inputBuffer `shouldBe` ""
|
|
|
|
|
|
|
|
it "should reset the scroll offset" $
|
|
|
|
result^.scrollOffset `shouldBe` 0
|
2019-10-15 00:16:44 -04:00
|
|
|
|
|
|
|
scrollUpSpec :: Spec
|
|
|
|
scrollUpSpec = describe "scrollUp" $ do
|
|
|
|
|
|
|
|
context "scrolled down" $
|
|
|
|
it "should decrease the scroll offset by one" $ let
|
|
|
|
ps = newProgState & scrollOffset .~ 10
|
|
|
|
ps' = scrollUp ps
|
|
|
|
in ps'^.scrollOffset `shouldBe` 9
|
|
|
|
|
|
|
|
context "at top" $
|
|
|
|
it "should keep the scroll offset at zero" $ let
|
|
|
|
ps = scrollUp newProgState
|
|
|
|
in ps^.scrollOffset `shouldBe` 0
|
|
|
|
|
|
|
|
context "above top" $
|
|
|
|
it "should return the scroll offset to zero" $ let
|
|
|
|
ps = newProgState & scrollOffset .~ (-10)
|
|
|
|
ps' = scrollUp ps
|
|
|
|
in ps'^.scrollOffset `shouldBe` 0
|
|
|
|
|
2019-11-07 22:36:08 -05:00
|
|
|
scrollDownSpec :: Spec
|
2019-10-15 00:16:44 -04:00
|
|
|
scrollDownSpec = describe "scrollDown" $
|
|
|
|
it "should increase the scroll offset" $ let
|
|
|
|
ps = newProgState & scrollOffset .~ 10
|
|
|
|
ps' = scrollDown ps
|
|
|
|
in ps'^.scrollOffset `shouldBe` 11
|