implemented addChar and removeChar
This commit is contained in:
parent
3cc76d881c
commit
054289e3d6
|
@ -19,6 +19,8 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
|
||||||
module Mtlstats.Actions
|
module Mtlstats.Actions
|
||||||
( startNewSeason
|
( startNewSeason
|
||||||
, resetYtd
|
, resetYtd
|
||||||
|
@ -49,8 +51,10 @@ startNewGame
|
||||||
|
|
||||||
-- | Adds a character to the input buffer
|
-- | Adds a character to the input buffer
|
||||||
addChar :: Char -> ProgState -> ProgState
|
addChar :: Char -> ProgState -> ProgState
|
||||||
addChar = undefined
|
addChar c = inputBuffer %~ (++[c])
|
||||||
|
|
||||||
-- | Removes a character from the input buffer (if possible)
|
-- | Removes a character from the input buffer (if possible)
|
||||||
removeChar :: ProgState -> ProgState
|
removeChar :: ProgState -> ProgState
|
||||||
removeChar = undefined
|
removeChar = inputBuffer %~ \case
|
||||||
|
"" -> ""
|
||||||
|
str -> init str
|
||||||
|
|
|
@ -34,6 +34,8 @@ spec = describe "Mtlstats.Actions" $ do
|
||||||
startNewSeasonSpec
|
startNewSeasonSpec
|
||||||
startNewGameSpec
|
startNewGameSpec
|
||||||
resetYtdSpec
|
resetYtdSpec
|
||||||
|
addCharSpec
|
||||||
|
removeCharSpec
|
||||||
|
|
||||||
startNewSeasonSpec :: Spec
|
startNewSeasonSpec :: Spec
|
||||||
startNewSeasonSpec = describe "startNewSeason" $ do
|
startNewSeasonSpec = describe "startNewSeason" $ do
|
||||||
|
@ -101,6 +103,29 @@ resetYtdSpec = describe "resetYtd" $
|
||||||
lt ^. gsTies `shouldNotBe` 0) $
|
lt ^. gsTies `shouldNotBe` 0) $
|
||||||
s ^. database . dbGoalies
|
s ^. database . dbGoalies
|
||||||
|
|
||||||
|
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"
|
||||||
|
|
||||||
makePlayer :: IO Player
|
makePlayer :: IO Player
|
||||||
makePlayer = Player
|
makePlayer = Player
|
||||||
<$> makeNum
|
<$> makeNum
|
||||||
|
|
Loading…
Reference in New Issue
Block a user