commit
683c36e2b6
|
@ -0,0 +1,70 @@
|
|||
{- |
|
||||
|
||||
mtlstats
|
||||
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
||||
<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/>.
|
||||
|
||||
-}
|
||||
|
||||
module Mtlstats.Actions.EditStandings
|
||||
( editStandings
|
||||
, editHomeStandings
|
||||
, editAwayStandings
|
||||
, editWins
|
||||
, editLosses
|
||||
, editOvertime
|
||||
, editGoalsFor
|
||||
, editGoalsAgainst
|
||||
) where
|
||||
|
||||
import Lens.Micro ((.~))
|
||||
|
||||
import Mtlstats.Types
|
||||
|
||||
-- | Enters edit standings mode
|
||||
editStandings :: ProgState -> ProgState
|
||||
editStandings = progMode .~ EditStandings ESMMenu
|
||||
|
||||
-- | Edits the home standings
|
||||
editHomeStandings :: ProgState -> ProgState
|
||||
editHomeStandings = progMode .~ EditStandings (ESMHome ESMSubMenu)
|
||||
|
||||
-- | Edits the road standings
|
||||
editAwayStandings :: ProgState -> ProgState
|
||||
editAwayStandings = progMode .~ EditStandings (ESMAway ESMSubMenu)
|
||||
|
||||
-- | Changes to edit wins mode
|
||||
editWins :: ProgState -> ProgState
|
||||
editWins = doEdit ESMEditWins
|
||||
|
||||
-- | Changes to edit losses mode
|
||||
editLosses :: ProgState -> ProgState
|
||||
editLosses = doEdit ESMEditLosses
|
||||
|
||||
-- | Changes to edit overtime mode
|
||||
editOvertime :: ProgState -> ProgState
|
||||
editOvertime = doEdit ESMEditOvertime
|
||||
|
||||
-- | Changes to edit goals for mode
|
||||
editGoalsFor :: ProgState -> ProgState
|
||||
editGoalsFor = doEdit ESMEditGoalsFor
|
||||
|
||||
-- | Changes to edit goals against mode
|
||||
editGoalsAgainst :: ProgState -> ProgState
|
||||
editGoalsAgainst = doEdit ESMEditGoalsAgainst
|
||||
|
||||
doEdit :: ESMSubMode -> ProgState -> ProgState
|
||||
doEdit = (progMode.editStandingsModeL.esmSubModeL .~)
|
|
@ -31,6 +31,7 @@ import qualified UI.NCurses as C
|
|||
import Mtlstats.Actions
|
||||
import Mtlstats.Control.EditGoalie
|
||||
import Mtlstats.Control.EditPlayer
|
||||
import Mtlstats.Control.EditStandings
|
||||
import Mtlstats.Control.NewGame
|
||||
import Mtlstats.Handlers
|
||||
import Mtlstats.Menu
|
||||
|
@ -54,8 +55,9 @@ dispatch s = case s^.progMode of
|
|||
| null $ cgs^.cgsNumber -> getGoalieNumC
|
||||
| null $ cgs^.cgsName -> getGoalieNameC
|
||||
| otherwise -> confirmCreateGoalieC
|
||||
EditPlayer eps -> editPlayerC eps
|
||||
EditGoalie egs -> editGoalieC egs
|
||||
EditPlayer eps -> editPlayerC eps
|
||||
EditGoalie egs -> editGoalieC egs
|
||||
(EditStandings esm) -> editStandingsC esm
|
||||
|
||||
mainMenuC :: Controller
|
||||
mainMenuC = Controller
|
||||
|
|
|
@ -0,0 +1,87 @@
|
|||
{- |
|
||||
|
||||
mtlstats
|
||||
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
||||
<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/>.
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Mtlstats.Control.EditStandings (editStandingsC) where
|
||||
|
||||
import Lens.Micro ((^.))
|
||||
import qualified UI.NCurses as C
|
||||
|
||||
import Mtlstats.Format
|
||||
import Mtlstats.Menu
|
||||
import Mtlstats.Menu.EditStandings
|
||||
import Mtlstats.Prompt
|
||||
import Mtlstats.Prompt.EditStandings
|
||||
import Mtlstats.Types
|
||||
import Mtlstats.Types.Menu
|
||||
|
||||
-- | Controller for the edit standings menu
|
||||
editStandingsC :: EditStandingsMode -> Controller
|
||||
editStandingsC = \case
|
||||
ESMMenu -> menuControllerWith header editStandingsMenu
|
||||
ESMHome m -> editHomeStandingsC m
|
||||
ESMAway m -> editAwayStandingsC m
|
||||
|
||||
editHomeStandingsC :: ESMSubMode -> Controller
|
||||
editHomeStandingsC = \case
|
||||
ESMSubMenu -> menuC editHomeStandingsMenu
|
||||
ESMEditWins -> promptC editHomeWinsPrompt
|
||||
ESMEditLosses -> promptC editHomeLossesPrompt
|
||||
ESMEditOvertime -> promptC editHomeOvertimePrompt
|
||||
ESMEditGoalsFor -> promptC editHomeGoalsForPrompt
|
||||
ESMEditGoalsAgainst -> promptC editHomeGoalsAgainstPrompt
|
||||
|
||||
editAwayStandingsC :: ESMSubMode -> Controller
|
||||
editAwayStandingsC = \case
|
||||
ESMSubMenu -> menuC editAwayStandingsMenu
|
||||
ESMEditWins -> promptC editAwayWinsPrompt
|
||||
ESMEditLosses -> promptC editAwayLossesPrompt
|
||||
ESMEditOvertime -> promptC editAwayOvertimePrompt
|
||||
ESMEditGoalsFor -> promptC editAwayGoalsForPrompt
|
||||
ESMEditGoalsAgainst -> promptC editAwayGoalsAgainstPrompt
|
||||
|
||||
menuC :: Menu () -> Controller
|
||||
menuC = menuControllerWith header
|
||||
|
||||
promptC :: Prompt -> Controller
|
||||
promptC = promptControllerWith header
|
||||
|
||||
header :: ProgState -> C.Update ()
|
||||
header = do
|
||||
db <- (^.database)
|
||||
let
|
||||
home = db^.dbHomeGameStats
|
||||
away = db^.dbAwayGameStats
|
||||
table = numTable [" W", " L", " OT", " GF", " GA"]
|
||||
[ ( "HOME", valsFor home )
|
||||
, ( "ROAD", valsFor away )
|
||||
]
|
||||
return $ C.drawString $ unlines $ table ++ [""]
|
||||
|
||||
valsFor :: GameStats -> [Int]
|
||||
valsFor gs =
|
||||
[ gs^.gmsWins
|
||||
, gs^.gmsLosses
|
||||
, gs^.gmsOvertime
|
||||
, gs^.gmsGoalsFor
|
||||
, gs^.gmsGoalsAgainst
|
||||
]
|
|
@ -44,6 +44,7 @@ import qualified UI.NCurses as C
|
|||
|
||||
import Mtlstats.Actions
|
||||
import qualified Mtlstats.Actions.NewGame.GoalieInput as GI
|
||||
import Mtlstats.Actions.EditStandings
|
||||
import Mtlstats.Config
|
||||
import Mtlstats.Types
|
||||
import Mtlstats.Types.Menu
|
||||
|
@ -180,6 +181,8 @@ editMenu = Menu "*** EDIT ***" ()
|
|||
modify editPlayer
|
||||
, MenuItem '4' "Edit Goalie" $
|
||||
modify editGoalie
|
||||
, MenuItem '5' "Edit Standings" $
|
||||
modify editStandings
|
||||
, MenuItem 'R' "Return to Main Menu" $
|
||||
modify backHome
|
||||
]
|
||||
|
|
|
@ -0,0 +1,64 @@
|
|||
{- |
|
||||
|
||||
mtlstats
|
||||
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
||||
<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/>.
|
||||
|
||||
-}
|
||||
|
||||
module Mtlstats.Menu.EditStandings
|
||||
( editStandingsMenu
|
||||
, editHomeStandingsMenu
|
||||
, editAwayStandingsMenu
|
||||
) where
|
||||
|
||||
import Control.Monad.Trans.State (modify)
|
||||
|
||||
import Mtlstats.Actions
|
||||
import Mtlstats.Actions.EditStandings
|
||||
import Mtlstats.Types.Menu
|
||||
|
||||
editStandingsMenu :: Menu ()
|
||||
editStandingsMenu = Menu "*** EDIT STANDINGS ***" ()
|
||||
[ MenuItem '1' "Edit home standings" $
|
||||
modify editHomeStandings
|
||||
, MenuItem '2' "Edit road standings" $
|
||||
modify editAwayStandings
|
||||
, MenuItem 'R' "Return to main menu" $
|
||||
modify backHome
|
||||
]
|
||||
|
||||
editHomeStandingsMenu :: Menu ()
|
||||
editHomeStandingsMenu = subMenu "HOME"
|
||||
|
||||
editAwayStandingsMenu :: Menu ()
|
||||
editAwayStandingsMenu = subMenu "ROAD"
|
||||
|
||||
subMenu :: String -> Menu ()
|
||||
subMenu str = Menu ("*** " ++ str ++ " STANDINGS ***") ()
|
||||
[ MenuItem '1' "Edit wins" $
|
||||
modify editWins
|
||||
, MenuItem '2' "Edit losses" $
|
||||
modify editLosses
|
||||
, MenuItem '3' "Edit overtime games" $
|
||||
modify editOvertime
|
||||
, MenuItem '4' "Edit goals for" $
|
||||
modify editGoalsFor
|
||||
, MenuItem '5' "Edit goals against" $
|
||||
modify editGoalsAgainst
|
||||
, MenuItem 'R' "Return to edit standings menu" $
|
||||
modify editStandings
|
||||
]
|
|
@ -0,0 +1,89 @@
|
|||
{- |
|
||||
|
||||
mtlstats
|
||||
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
||||
<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/>.
|
||||
|
||||
-}
|
||||
|
||||
module Mtlstats.Prompt.EditStandings
|
||||
( editHomeWinsPrompt
|
||||
, editHomeLossesPrompt
|
||||
, editHomeOvertimePrompt
|
||||
, editHomeGoalsForPrompt
|
||||
, editHomeGoalsAgainstPrompt
|
||||
, editAwayWinsPrompt
|
||||
, editAwayLossesPrompt
|
||||
, editAwayOvertimePrompt
|
||||
, editAwayGoalsForPrompt
|
||||
, editAwayGoalsAgainstPrompt
|
||||
) where
|
||||
|
||||
import Control.Monad.Trans.State (modify)
|
||||
import Lens.Micro ((.~), (%~))
|
||||
|
||||
import Mtlstats.Prompt
|
||||
import Mtlstats.Types
|
||||
|
||||
editHomeWinsPrompt :: Prompt
|
||||
editHomeWinsPrompt =
|
||||
mkPrompt "Home wins: " (dbHomeGameStats.gmsWins .~)
|
||||
|
||||
editHomeLossesPrompt :: Prompt
|
||||
editHomeLossesPrompt =
|
||||
mkPrompt "Home losses: " (dbHomeGameStats.gmsLosses .~)
|
||||
|
||||
editHomeOvertimePrompt :: Prompt
|
||||
editHomeOvertimePrompt =
|
||||
mkPrompt "Home overtime games: " (dbHomeGameStats.gmsOvertime .~)
|
||||
|
||||
editHomeGoalsForPrompt :: Prompt
|
||||
editHomeGoalsForPrompt =
|
||||
mkPrompt "Home goals for: " (dbHomeGameStats.gmsGoalsFor .~)
|
||||
|
||||
editHomeGoalsAgainstPrompt :: Prompt
|
||||
editHomeGoalsAgainstPrompt =
|
||||
mkPrompt "Home goals against: " (dbHomeGameStats.gmsGoalsAgainst .~)
|
||||
|
||||
editAwayWinsPrompt :: Prompt
|
||||
editAwayWinsPrompt =
|
||||
mkPrompt "Road wins: " (dbAwayGameStats.gmsWins .~)
|
||||
|
||||
editAwayLossesPrompt :: Prompt
|
||||
editAwayLossesPrompt =
|
||||
mkPrompt "Road losses: " (dbAwayGameStats.gmsLosses .~)
|
||||
|
||||
editAwayOvertimePrompt :: Prompt
|
||||
editAwayOvertimePrompt =
|
||||
mkPrompt "Road overtime games: " (dbAwayGameStats.gmsOvertime .~)
|
||||
|
||||
editAwayGoalsForPrompt :: Prompt
|
||||
editAwayGoalsForPrompt =
|
||||
mkPrompt "Road goals for: " (dbAwayGameStats.gmsGoalsFor .~)
|
||||
|
||||
editAwayGoalsAgainstPrompt :: Prompt
|
||||
editAwayGoalsAgainstPrompt =
|
||||
mkPrompt "Road goals against: " (dbAwayGameStats.gmsGoalsAgainst .~)
|
||||
|
||||
mkPrompt :: String -> (Int -> Database -> Database) -> Prompt
|
||||
mkPrompt pStr f = numPromptWithFallback pStr
|
||||
(modify subMenu)
|
||||
(\n -> modify
|
||||
$ (database %~ f n)
|
||||
. subMenu)
|
||||
|
||||
subMenu :: ProgState -> ProgState
|
||||
subMenu = progMode.editStandingsModeL.esmSubModeL .~ ESMSubMenu
|
|
@ -35,6 +35,8 @@ module Mtlstats.Types (
|
|||
EditPlayerMode (..),
|
||||
EditGoalieState (..),
|
||||
EditGoalieMode (..),
|
||||
EditStandingsMode (..),
|
||||
ESMSubMode (..),
|
||||
Database (..),
|
||||
Player (..),
|
||||
PlayerStats (..),
|
||||
|
@ -56,6 +58,9 @@ module Mtlstats.Types (
|
|||
createGoalieStateL,
|
||||
editPlayerStateL,
|
||||
editGoalieStateL,
|
||||
editStandingsModeL,
|
||||
-- ** EditStandingsMode Lenses
|
||||
esmSubModeL,
|
||||
-- ** GameState Lenses
|
||||
gameYear,
|
||||
gameMonth,
|
||||
|
@ -239,16 +244,18 @@ data ProgMode
|
|||
| CreateGoalie CreateGoalieState
|
||||
| EditPlayer EditPlayerState
|
||||
| EditGoalie EditGoalieState
|
||||
| EditStandings EditStandingsMode
|
||||
|
||||
instance Show ProgMode where
|
||||
show MainMenu = "MainMenu"
|
||||
show (NewSeason _) = "NewSeason"
|
||||
show (NewGame _) = "NewGame"
|
||||
show EditMenu = "EditMenu"
|
||||
show (CreatePlayer _) = "CreatePlayer"
|
||||
show (CreateGoalie _) = "CreateGoalie"
|
||||
show (EditPlayer _) = "EditPlayer"
|
||||
show (EditGoalie _) = "EditGoalie"
|
||||
show MainMenu = "MainMenu"
|
||||
show (NewSeason _) = "NewSeason"
|
||||
show (NewGame _) = "NewGame"
|
||||
show EditMenu = "EditMenu"
|
||||
show (CreatePlayer _) = "CreatePlayer"
|
||||
show (CreateGoalie _) = "CreateGoalie"
|
||||
show (EditPlayer _) = "EditPlayer"
|
||||
show (EditGoalie _) = "EditGoalie"
|
||||
show (EditStandings _) = "EditStandings"
|
||||
|
||||
-- | The game state
|
||||
data GameState = GameState
|
||||
|
@ -389,6 +396,23 @@ data EditGoalieMode
|
|||
| EGLtTies
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Represents the standings edit mode
|
||||
data EditStandingsMode
|
||||
= ESMMenu
|
||||
| ESMHome ESMSubMode
|
||||
| ESMAway ESMSubMode
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Represents the standings edit sub-mode
|
||||
data ESMSubMode
|
||||
= ESMSubMenu
|
||||
| ESMEditWins
|
||||
| ESMEditLosses
|
||||
| ESMEditOvertime
|
||||
| ESMEditGoalsFor
|
||||
| ESMEditGoalsAgainst
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Represents the database
|
||||
data Database = Database
|
||||
{ _dbPlayers :: [Player]
|
||||
|
@ -714,6 +738,24 @@ editGoalieStateL = lens
|
|||
_ -> newEditGoalieState)
|
||||
(\_ egs -> EditGoalie egs)
|
||||
|
||||
editStandingsModeL :: Lens' ProgMode EditStandingsMode
|
||||
editStandingsModeL = lens
|
||||
(\case
|
||||
EditStandings esm -> esm
|
||||
_ -> ESMMenu)
|
||||
(\_ esm -> EditStandings esm)
|
||||
|
||||
esmSubModeL :: Lens' EditStandingsMode ESMSubMode
|
||||
esmSubModeL = lens
|
||||
(\case
|
||||
ESMMenu -> ESMSubMenu
|
||||
ESMHome m -> m
|
||||
ESMAway m -> m)
|
||||
(\mode subMode -> case mode of
|
||||
ESMMenu -> ESMMenu
|
||||
ESMHome _ -> ESMHome subMode
|
||||
ESMAway _ -> ESMAway subMode)
|
||||
|
||||
-- | Constructor for a 'ProgState'
|
||||
newProgState :: ProgState
|
||||
newProgState = ProgState
|
||||
|
|
|
@ -0,0 +1,83 @@
|
|||
{-
|
||||
|
||||
mtlstats
|
||||
Copyright (C) 1984, 1985, 2019, 2020 Rhéal Lamothe
|
||||
<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/>.
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Actions.EditStandingsSpec (spec) where
|
||||
|
||||
import Lens.Micro ((^.), (&), (.~))
|
||||
import Test.Hspec
|
||||
( Spec
|
||||
, context
|
||||
, describe
|
||||
, it
|
||||
, shouldBe
|
||||
, shouldSatisfy
|
||||
)
|
||||
|
||||
import Mtlstats.Actions.EditStandings
|
||||
import Mtlstats.Types
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "EditStandings" $ do
|
||||
mapM_
|
||||
(\(label, f, expected) -> describe label $ do
|
||||
let
|
||||
ps = newProgState
|
||||
ps' = f ps
|
||||
|
||||
it "should set progMode to EditStandings" $
|
||||
ps'^.progMode `shouldSatisfy` \case
|
||||
(EditStandings _) -> True
|
||||
_ -> False
|
||||
|
||||
it ("should set editStandingsMode to " ++ show expected) $
|
||||
ps'^.progMode.editStandingsModeL `shouldBe` expected)
|
||||
|
||||
-- label, function, expected mode
|
||||
[ ( "editStandings", editStandings, ESMMenu )
|
||||
, ( "editHomeStandings", editHomeStandings, ESMHome ESMSubMenu )
|
||||
, ( "editAwayStandings", editAwayStandings, ESMAway ESMSubMenu )
|
||||
]
|
||||
|
||||
mapM_
|
||||
(\(label, f, expected) -> describe label $ do
|
||||
mapM_
|
||||
(\prefix -> context ("mode: " ++ show (prefix ESMSubMenu)) $ let
|
||||
ps = newProgState & progMode.editStandingsModeL .~ prefix ESMSubMenu
|
||||
ps' = f ps
|
||||
in it ("should set the mode to " ++ show expected) $
|
||||
ps'^.progMode.editStandingsModeL `shouldBe` prefix expected)
|
||||
[ESMHome, ESMAway]
|
||||
|
||||
context "mode: ESMMenu" $ let
|
||||
ps = newProgState & progMode.editStandingsModeL .~ ESMMenu
|
||||
ps' = f ps
|
||||
in it "should not change the mode" $
|
||||
ps'^.progMode.editStandingsModeL `shouldBe` ESMMenu)
|
||||
|
||||
-- label, function, expected
|
||||
[ ( "editWins", editWins, ESMEditWins )
|
||||
, ( "editLosses", editLosses, ESMEditLosses )
|
||||
, ( "editOvertime", editOvertime, ESMEditOvertime )
|
||||
, ( "editGoalsFor", editGoalsFor, ESMEditGoalsFor )
|
||||
, ( "editGoalsAgainst", editGoalsAgainst, ESMEditGoalsAgainst )
|
||||
]
|
|
@ -39,6 +39,7 @@ import Mtlstats.Actions
|
|||
import Mtlstats.Types
|
||||
|
||||
import qualified Actions.NewGameSpec as NewGame
|
||||
import qualified Actions.EditStandingsSpec as EditStandings
|
||||
import qualified TypesSpec as TS
|
||||
|
||||
spec :: Spec
|
||||
|
@ -65,6 +66,7 @@ spec = describe "Mtlstats.Actions" $ do
|
|||
scrollUpSpec
|
||||
scrollDownSpec
|
||||
NewGame.spec
|
||||
EditStandings.spec
|
||||
|
||||
startNewSeasonSpec :: Spec
|
||||
startNewSeasonSpec = describe "startNewSeason" $ do
|
||||
|
|
|
@ -58,6 +58,8 @@ spec = describe "Mtlstats.Types" $ do
|
|||
createGoalieStateLSpec
|
||||
editPlayerStateLSpec
|
||||
editGoalieStateLSpec
|
||||
editStandingsModeLSpec
|
||||
esmSubModeLSpec
|
||||
teamScoreSpec
|
||||
otherScoreSpec
|
||||
homeTeamSpec
|
||||
|
@ -191,6 +193,47 @@ editGoalieStateLSpec = describe "editGoalieStateL" $
|
|||
egs2 = newEditGoalieState
|
||||
& egsSelectedGoalie ?~ 2
|
||||
|
||||
editStandingsModeLSpec :: Spec
|
||||
editStandingsModeLSpec = describe "editStandingsModeL" $
|
||||
lensSpec editStandingsModeL
|
||||
-- getters
|
||||
[ ( "missing mode", MainMenu, menu )
|
||||
, ( "with mode", EditStandings home, home )
|
||||
]
|
||||
-- setters
|
||||
[ ( "set mode", MainMenu, home )
|
||||
, ( "change mode", EditStandings home, away )
|
||||
]
|
||||
where
|
||||
menu = ESMMenu
|
||||
home = ESMHome ESMSubMenu
|
||||
away = ESMAway ESMSubMenu
|
||||
|
||||
esmSubModeLSpec :: Spec
|
||||
esmSubModeLSpec = describe "esmSubModeL" $ do
|
||||
|
||||
context "getters" $ mapM_
|
||||
(\(label, mode, expected) -> context label $
|
||||
it ("should be " ++ show expected) $
|
||||
mode^.esmSubModeL `shouldBe` expected)
|
||||
|
||||
-- label, mode, expected
|
||||
[ ( "no state", ESMMenu, ESMSubMenu )
|
||||
, ( "with state", ESMHome ESMEditWins, ESMEditWins )
|
||||
]
|
||||
|
||||
context "setters" $ mapM_
|
||||
(\(label, mode, expected) -> context label $
|
||||
it ("should be " ++ show expected) $ let
|
||||
mode' = mode & esmSubModeL .~ ESMEditWins
|
||||
in mode' `shouldBe` expected)
|
||||
|
||||
-- label, mode, expected
|
||||
[ ( "no state", ESMMenu, ESMMenu )
|
||||
, ( "home mode", ESMHome ESMSubMenu, ESMHome ESMEditWins )
|
||||
, ( "away mode", ESMAway ESMSubMenu, ESMAway ESMEditWins )
|
||||
]
|
||||
|
||||
teamScoreSpec :: Spec
|
||||
teamScoreSpec = describe "teamScore" $ do
|
||||
let
|
||||
|
@ -957,3 +1000,8 @@ instance Comparable CreateGoalieState where
|
|||
describe "cgsName" $
|
||||
it ("should be " ++ expected^.cgsName) $
|
||||
actual^.cgsName `shouldBe` expected^.cgsName
|
||||
|
||||
instance Comparable EditStandingsMode where
|
||||
compareTest actual expected =
|
||||
it ("should be " ++ show expected) $
|
||||
actual `shouldBe` expected
|
||||
|
|
Loading…
Reference in New Issue
Block a user