implemented editHomeStandings
This commit is contained in:
@@ -31,11 +31,11 @@ import Mtlstats.Types
|
|||||||
|
|
||||||
-- | Enters edit standings mode
|
-- | Enters edit standings mode
|
||||||
editStandings :: ProgState -> ProgState
|
editStandings :: ProgState -> ProgState
|
||||||
editStandings = progMode .~ EditStandings
|
editStandings = progMode .~ EditStandings ESMMenu
|
||||||
|
|
||||||
-- | Edits the home standings
|
-- | Edits the home standings
|
||||||
editHomeStandings :: ProgState -> ProgState
|
editHomeStandings :: ProgState -> ProgState
|
||||||
editHomeStandings = undefined
|
editHomeStandings = progMode .~ EditStandings ESMHome
|
||||||
|
|
||||||
-- | Edits the road standings
|
-- | Edits the road standings
|
||||||
editRoadStandings :: ProgState -> ProgState
|
editRoadStandings :: ProgState -> ProgState
|
||||||
|
|||||||
@@ -55,9 +55,9 @@ dispatch s = case s^.progMode of
|
|||||||
| null $ cgs^.cgsNumber -> getGoalieNumC
|
| null $ cgs^.cgsNumber -> getGoalieNumC
|
||||||
| null $ cgs^.cgsName -> getGoalieNameC
|
| null $ cgs^.cgsName -> getGoalieNameC
|
||||||
| otherwise -> confirmCreateGoalieC
|
| otherwise -> confirmCreateGoalieC
|
||||||
EditPlayer eps -> editPlayerC eps
|
EditPlayer eps -> editPlayerC eps
|
||||||
EditGoalie egs -> editGoalieC egs
|
EditGoalie egs -> editGoalieC egs
|
||||||
EditStandings -> editStandingsC
|
(EditStandings esm) -> editStandingsC esm
|
||||||
|
|
||||||
mainMenuC :: Controller
|
mainMenuC :: Controller
|
||||||
mainMenuC = Controller
|
mainMenuC = Controller
|
||||||
|
|||||||
@@ -19,6 +19,8 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
|
||||||
module Mtlstats.Control.EditStandings (editStandingsC) where
|
module Mtlstats.Control.EditStandings (editStandingsC) where
|
||||||
|
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.))
|
||||||
@@ -30,8 +32,13 @@ import Mtlstats.Menu.EditStandings
|
|||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
|
|
||||||
-- | Controller for the edit standings menu
|
-- | Controller for the edit standings menu
|
||||||
editStandingsC :: Controller
|
editStandingsC :: EditStandingsMode -> Controller
|
||||||
editStandingsC = menuControllerWith header editStandingsMenu
|
editStandingsC = \case
|
||||||
|
ESMMenu -> menuControllerWith header editStandingsMenu
|
||||||
|
ESMHome -> editHomeStandingsC
|
||||||
|
|
||||||
|
editHomeStandingsC :: Controller
|
||||||
|
editHomeStandingsC = undefined
|
||||||
|
|
||||||
header :: ProgState -> C.Update ()
|
header :: ProgState -> C.Update ()
|
||||||
header = do
|
header = do
|
||||||
|
|||||||
@@ -35,6 +35,7 @@ module Mtlstats.Types (
|
|||||||
EditPlayerMode (..),
|
EditPlayerMode (..),
|
||||||
EditGoalieState (..),
|
EditGoalieState (..),
|
||||||
EditGoalieMode (..),
|
EditGoalieMode (..),
|
||||||
|
EditStandingsMode (..),
|
||||||
Database (..),
|
Database (..),
|
||||||
Player (..),
|
Player (..),
|
||||||
PlayerStats (..),
|
PlayerStats (..),
|
||||||
@@ -56,6 +57,7 @@ module Mtlstats.Types (
|
|||||||
createGoalieStateL,
|
createGoalieStateL,
|
||||||
editPlayerStateL,
|
editPlayerStateL,
|
||||||
editGoalieStateL,
|
editGoalieStateL,
|
||||||
|
editStandingsModeL,
|
||||||
-- ** GameState Lenses
|
-- ** GameState Lenses
|
||||||
gameYear,
|
gameYear,
|
||||||
gameMonth,
|
gameMonth,
|
||||||
@@ -239,18 +241,18 @@ data ProgMode
|
|||||||
| CreateGoalie CreateGoalieState
|
| CreateGoalie CreateGoalieState
|
||||||
| EditPlayer EditPlayerState
|
| EditPlayer EditPlayerState
|
||||||
| EditGoalie EditGoalieState
|
| EditGoalie EditGoalieState
|
||||||
| EditStandings
|
| EditStandings EditStandingsMode
|
||||||
|
|
||||||
instance Show ProgMode where
|
instance Show ProgMode where
|
||||||
show MainMenu = "MainMenu"
|
show MainMenu = "MainMenu"
|
||||||
show (NewSeason _) = "NewSeason"
|
show (NewSeason _) = "NewSeason"
|
||||||
show (NewGame _) = "NewGame"
|
show (NewGame _) = "NewGame"
|
||||||
show EditMenu = "EditMenu"
|
show EditMenu = "EditMenu"
|
||||||
show (CreatePlayer _) = "CreatePlayer"
|
show (CreatePlayer _) = "CreatePlayer"
|
||||||
show (CreateGoalie _) = "CreateGoalie"
|
show (CreateGoalie _) = "CreateGoalie"
|
||||||
show (EditPlayer _) = "EditPlayer"
|
show (EditPlayer _) = "EditPlayer"
|
||||||
show (EditGoalie _) = "EditGoalie"
|
show (EditGoalie _) = "EditGoalie"
|
||||||
show EditStandings = "EditStandings"
|
show (EditStandings _) = "EditStandings"
|
||||||
|
|
||||||
-- | The game state
|
-- | The game state
|
||||||
data GameState = GameState
|
data GameState = GameState
|
||||||
@@ -391,6 +393,12 @@ data EditGoalieMode
|
|||||||
| EGLtTies
|
| EGLtTies
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
-- | Represents the standings edit mode
|
||||||
|
data EditStandingsMode
|
||||||
|
= ESMMenu
|
||||||
|
| ESMHome
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
-- | Represents the database
|
-- | Represents the database
|
||||||
data Database = Database
|
data Database = Database
|
||||||
{ _dbPlayers :: [Player]
|
{ _dbPlayers :: [Player]
|
||||||
@@ -716,6 +724,13 @@ editGoalieStateL = lens
|
|||||||
_ -> newEditGoalieState)
|
_ -> newEditGoalieState)
|
||||||
(\_ egs -> EditGoalie egs)
|
(\_ egs -> EditGoalie egs)
|
||||||
|
|
||||||
|
editStandingsModeL :: Lens' ProgMode EditStandingsMode
|
||||||
|
editStandingsModeL = lens
|
||||||
|
(\case
|
||||||
|
EditStandings esm -> esm
|
||||||
|
_ -> ESMMenu)
|
||||||
|
(\_ esm -> EditStandings esm)
|
||||||
|
|
||||||
-- | Constructor for a 'ProgState'
|
-- | Constructor for a 'ProgState'
|
||||||
newProgState :: ProgState
|
newProgState :: ProgState
|
||||||
newProgState = ProgState
|
newProgState = ProgState
|
||||||
|
|||||||
@@ -24,20 +24,27 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||||||
module Actions.EditStandingsSpec (spec) where
|
module Actions.EditStandingsSpec (spec) where
|
||||||
|
|
||||||
import Lens.Micro ((^.))
|
import Lens.Micro ((^.))
|
||||||
import Test.Hspec (Spec, describe, it, shouldSatisfy)
|
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
|
||||||
|
|
||||||
import Mtlstats.Actions.EditStandings
|
import Mtlstats.Actions.EditStandings
|
||||||
import Mtlstats.Types
|
import Mtlstats.Types
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = describe "EditStandings"
|
spec = describe "EditStandings" $ mapM_
|
||||||
editStandingsSpec
|
(\(label, f, expected) -> describe label $ do
|
||||||
|
let
|
||||||
|
ps = newProgState
|
||||||
|
ps' = f ps
|
||||||
|
|
||||||
editStandingsSpec :: Spec
|
it "should set progMode to EditStandings" $
|
||||||
editStandingsSpec = describe "editStandings" $ let
|
ps'^.progMode `shouldSatisfy` \case
|
||||||
ps = newProgState
|
(EditStandings _) -> True
|
||||||
ps' = editStandings ps
|
_ -> False
|
||||||
in it "should set progMode to EditStandings" $
|
|
||||||
ps'^.progMode `shouldSatisfy` \case
|
it ("should set editStandingsMode to " ++ show expected) $
|
||||||
EditStandings -> True
|
ps'^.progMode.editStandingsModeL `shouldBe` expected)
|
||||||
_ -> False
|
|
||||||
|
-- label, function, expected mode
|
||||||
|
[ ( "editStandings", editStandings, ESMMenu )
|
||||||
|
, ( "editHomeStandings", editHomeStandings, ESMHome )
|
||||||
|
]
|
||||||
|
|||||||
@@ -58,6 +58,7 @@ spec = describe "Mtlstats.Types" $ do
|
|||||||
createGoalieStateLSpec
|
createGoalieStateLSpec
|
||||||
editPlayerStateLSpec
|
editPlayerStateLSpec
|
||||||
editGoalieStateLSpec
|
editGoalieStateLSpec
|
||||||
|
editStandingsModeLSpec
|
||||||
teamScoreSpec
|
teamScoreSpec
|
||||||
otherScoreSpec
|
otherScoreSpec
|
||||||
homeTeamSpec
|
homeTeamSpec
|
||||||
@@ -191,6 +192,18 @@ editGoalieStateLSpec = describe "editGoalieStateL" $
|
|||||||
egs2 = newEditGoalieState
|
egs2 = newEditGoalieState
|
||||||
& egsSelectedGoalie ?~ 2
|
& egsSelectedGoalie ?~ 2
|
||||||
|
|
||||||
|
editStandingsModeLSpec :: Spec
|
||||||
|
editStandingsModeLSpec = describe "editStandingsModeL" $
|
||||||
|
lensSpec editStandingsModeL
|
||||||
|
-- getters
|
||||||
|
[ ( "missing mode", MainMenu, ESMMenu )
|
||||||
|
, ( "with mode", EditStandings ESMHome, ESMHome )
|
||||||
|
]
|
||||||
|
-- setters
|
||||||
|
[ ( "set mode", MainMenu, ESMHome )
|
||||||
|
, ( "change mode", EditStandings ESMMenu, ESMHome )
|
||||||
|
]
|
||||||
|
|
||||||
teamScoreSpec :: Spec
|
teamScoreSpec :: Spec
|
||||||
teamScoreSpec = describe "teamScore" $ do
|
teamScoreSpec = describe "teamScore" $ do
|
||||||
let
|
let
|
||||||
@@ -957,3 +970,8 @@ instance Comparable CreateGoalieState where
|
|||||||
describe "cgsName" $
|
describe "cgsName" $
|
||||||
it ("should be " ++ expected^.cgsName) $
|
it ("should be " ++ expected^.cgsName) $
|
||||||
actual^.cgsName `shouldBe` expected^.cgsName
|
actual^.cgsName `shouldBe` expected^.cgsName
|
||||||
|
|
||||||
|
instance Comparable EditStandingsMode where
|
||||||
|
compareTest actual expected =
|
||||||
|
it ("should be " ++ show expected) $
|
||||||
|
actual `shouldBe` expected
|
||||||
|
|||||||
Reference in New Issue
Block a user