Merge pull request #60 from mtlstats/rookie-col

Add rookie flag to players/goalies
This commit is contained in:
Jonathan Lamothe 2020-01-09 01:54:48 -05:00 committed by GitHub
commit 119c28ef18
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
13 changed files with 358 additions and 193 deletions

View File

@ -32,7 +32,9 @@ module Mtlstats.Actions
, createGoalie
, edit
, editPlayer
, editSelectedPlayer
, editGoalie
, editSelectedGoalie
, addPlayer
, addGoalie
, resetCreatePlayerState
@ -47,6 +49,7 @@ import Data.Maybe (fromMaybe)
import Lens.Micro ((^.), (&), (.~), (%~))
import Mtlstats.Types
import Mtlstats.Util
-- | Starts a new season
startNewSeason :: ProgState -> ProgState
@ -106,10 +109,36 @@ edit = progMode .~ EditMenu
editPlayer :: ProgState -> ProgState
editPlayer = progMode .~ EditPlayer newEditPlayerState
-- | Edits the selected 'Player'
editSelectedPlayer
:: (Player -> Player)
-- ^ The modification to be made to the 'Player'
-> ProgState
-> ProgState
editSelectedPlayer f s = fromMaybe s $ do
n <- s^.progMode.editPlayerStateL.epsSelectedPlayer
let
players = s^.database.dbPlayers
players' = modifyNth n f players
Just $ s & database.dbPlayers .~ players'
-- | Starts the 'Goalie' editing process
editGoalie :: ProgState -> ProgState
editGoalie = progMode .~ EditGoalie newEditGoalieState
-- | Edits the selected 'Goalie'
editSelectedGoalie
:: (Goalie -> Goalie)
-- ^ The modification to be made to the 'Goalie'
-> ProgState
-> ProgState
editSelectedGoalie f s = fromMaybe s $ do
n <- s^.progMode.editGoalieStateL.egsSelectedGoalie
let
goalies = s^.database.dbGoalies
goalies' = modifyNth n f goalies
Just $ s & database.dbGoalies .~ goalies'
-- | Adds the entered player to the roster
addPlayer :: ProgState -> ProgState
addPlayer s = fromMaybe s $ do

View File

@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
module Mtlstats.Helpers.Goalie (goalieDetails) where
module Mtlstats.Helpers.Goalie (goalieDetails, goalieName) where
import Lens.Micro ((^.))
@ -31,7 +31,7 @@ goalieDetails :: Goalie -> String
goalieDetails g = let
header = unlines $ labelTable
[ ( "Number", show $ g^.gNumber )
, ( "Name", g^.gName )
, ( "Name", goalieName g )
]
body = unlines $ numTable ["YTD", "Lifetime"] $ map
@ -46,3 +46,13 @@ goalieDetails g = let
]
in header ++ "\n" ++ body
-- | Returns the goalie name, modified if they are a rookie
goalieName :: Goalie -> String
goalieName g = let
suffix = if g^.gRookie
then "*"
else ""
in g^.gName ++ suffix

View File

@ -19,7 +19,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
module Mtlstats.Helpers.Player (playerDetails) where
module Mtlstats.Helpers.Player (playerDetails, playerName) where
import Lens.Micro ((^.))
@ -32,7 +32,7 @@ playerDetails p = unlines $ top ++ [""] ++ table
where
top = labelTable
[ ( "Number", show $ p^.pNumber )
, ( "Name", p^.pName )
, ( "Name", playerName p )
, ( "Position", p^.pPosition )
]
@ -43,3 +43,14 @@ playerDetails p = unlines $ top ++ [""] ++ table
, ( "Assists", psAssists )
, ( "Penalty mins", psPMin )
]
-- | Presents a modified version of the player's name indicating
-- whether or not they're a rookie
playerName :: Player -> String
playerName p = let
suffix = if p^.pRookie
then "*"
else ""
in p^.pName ++ suffix

View File

@ -26,7 +26,7 @@ module Mtlstats.Menu.EditGoalie
) where
import Control.Monad.Trans.State (modify)
import Lens.Micro ((.~))
import Lens.Micro ((.~), (%~))
import Mtlstats.Actions
import Mtlstats.Types
@ -35,18 +35,21 @@ import Mtlstats.Types.Menu
-- | The 'Goalie' edit menu
editGoalieMenu :: Menu ()
editGoalieMenu = Menu "*** EDIT GOALTENDER ***" () $ map
(\(ch, label, mode) -> MenuItem ch label $
modify $ case mode of
Nothing -> edit
Just m -> progMode.editGoalieStateL.egsMode .~ m)
(\(ch, label, action) -> MenuItem ch label $ modify action)
-- key, label, value
[ ( '1', "Edit number", Just EGNumber )
, ( '2', "Edit name", Just EGName )
, ( '3', "Edit YTD stats", Just EGYtd )
, ( '4', "Edit Lifetime stats", Just EGLifetime )
, ( 'R', "Return to Edit Menu", Nothing )
[ ( '1', "Edit number", set EGNumber )
, ( '2', "Edit name", set EGName )
, ( '3', "Toggle rookie flag", toggle )
, ( '4', "Edit YTD stats", set EGYtd )
, ( '5', "Edit Lifetime stats", set EGLifetime )
, ( 'R', "Return to Edit Menu", edit )
]
where
set mode = progMode.editGoalieStateL.egsMode .~ mode
toggle = editSelectedGoalie (gRookie %~ not)
-- | The 'Goalie' YTD edit menu
editGoalieYtdMenu :: Menu ()
editGoalieYtdMenu = editMenu "*** EDIT GOALTENDER YEAR-TO-DATE ***"

View File

@ -26,7 +26,7 @@ module Mtlstats.Menu.EditPlayer
) where
import Control.Monad.Trans.State (modify)
import Lens.Micro ((.~))
import Lens.Micro ((.~), (%~))
import Mtlstats.Actions
import Mtlstats.Types
@ -35,19 +35,22 @@ import Mtlstats.Types.Menu
-- | The 'Player' edit menu
editPlayerMenu :: Menu ()
editPlayerMenu = Menu "*** EDIT PLAYER ***" () $ map
(\(ch, label, mode) -> MenuItem ch label $
modify $ case mode of
Nothing -> edit
Just m -> progMode.editPlayerStateL.epsMode .~ m)
(\(ch, label, action) -> MenuItem ch label $ modify action)
-- key, label, value
[ ( '1', "Edit number", Just EPNumber )
, ( '2', "Edit name", Just EPName )
, ( '3', "Edit position", Just EPPosition )
, ( '4', "Edit YTD stats", Just EPYtd )
, ( '5', "Edit lifetime stats", Just EPLifetime )
, ( 'R', "Return to Edit Menu", Nothing )
[ ( '1', "Edit number", set EPNumber )
, ( '2', "Edit name", set EPName )
, ( '3', "Edit position", set EPPosition )
, ( '4', "Toggle rookie flag", toggle )
, ( '5', "Edit YTD stats", set EPYtd )
, ( '6', "Edit lifetime stats", set EPLifetime )
, ( 'R', "Return to Edit Menu", edit )
]
where
set mode = progMode.editPlayerStateL.epsMode .~ mode
toggle = editSelectedPlayer $ pRookie %~ not
-- | The 'Player' YTD stats edit menu
editPlayerYtdMenu :: Menu ()
editPlayerYtdMenu = editMenu

View File

@ -39,13 +39,12 @@ module Mtlstats.Prompt.EditGoalie
, editGoalieLtTiesPrompt
) where
import Control.Monad.Extra (whenJustM)
import Control.Monad.Trans.State (gets, modify)
import Lens.Micro ((^.), (.~), (%~))
import Control.Monad.Trans.State (modify)
import Lens.Micro ((.~))
import Mtlstats.Actions
import Mtlstats.Prompt
import Mtlstats.Types
import Mtlstats.Util
-- | Prompt to select a 'Goalie' for editing
goalieToEditPrompt :: Prompt
@ -62,7 +61,7 @@ editGoalieNamePrompt :: Prompt
editGoalieNamePrompt = namePrompt "Goalie name: " $ \name ->
if null name
then goto EGMenu
else editGoalie EGMenu $ gName .~ name
else doEdit EGMenu $ gName .~ name
-- | Prompt to edit a goalie's YTD games played
editGoalieYtdGamesPrompt
@ -213,13 +212,12 @@ editNum
-> Prompt
editNum pStr mode f = numPromptWithFallback pStr
(goto mode)
(editGoalie mode . f)
(doEdit mode . f)
editGoalie :: EditGoalieMode -> (Goalie -> Goalie) -> Action ()
editGoalie mode f =
whenJustM (gets (^.progMode.editGoalieStateL.egsSelectedGoalie)) $ \gid -> do
modify $ database.dbGoalies %~ modifyNth gid f
goto mode
doEdit :: EditGoalieMode -> (Goalie -> Goalie) -> Action ()
doEdit mode f = do
modify $ editSelectedGoalie f
goto mode
goto :: EditGoalieMode -> Action ()
goto = modify . (progMode.editGoalieStateL.egsMode .~)

View File

@ -31,13 +31,12 @@ module Mtlstats.Prompt.EditPlayer
, editPlayerLtPMinPrompt
) where
import Control.Monad.Extra (whenJustM)
import Control.Monad.Trans.State (gets, modify)
import Lens.Micro ((^.), (.~), (%~))
import Control.Monad.Trans.State (modify)
import Lens.Micro ((.~))
import Mtlstats.Actions
import Mtlstats.Prompt
import Mtlstats.Types
import Mtlstats.Util
-- | Prompt to edit a player's number
editPlayerNumPrompt :: Prompt
@ -49,14 +48,14 @@ editPlayerNamePrompt :: Prompt
editPlayerNamePrompt = namePrompt "Player name: " $ \name ->
if null name
then goto EPMenu
else editPlayer EPMenu $ pName .~ name
else doEdit EPMenu $ pName .~ name
-- | Prompt to edit a player's position
editPlayerPosPrompt :: Prompt
editPlayerPosPrompt = ucStrPrompt "Player position: " $ \pos ->
if null pos
then goto EPMenu
else editPlayer EPMenu $ pPosition .~ pos
else doEdit EPMenu $ pPosition .~ pos
-- | Prompt to edit a player's year-to-date goals
editPlayerYtdGoalsPrompt
@ -115,13 +114,12 @@ editNum
-> Prompt
editNum pStr mode f = numPromptWithFallback pStr
(goto mode)
(editPlayer mode . f)
(doEdit mode . f)
editPlayer :: EditPlayerMode -> (Player -> Player) -> Action ()
editPlayer mode f =
whenJustM (gets (^.progMode.editPlayerStateL.epsSelectedPlayer)) $ \pid -> do
modify $ database.dbPlayers %~ modifyNth pid f
goto mode
doEdit :: EditPlayerMode -> (Player -> Player) -> Action ()
doEdit mode f = do
modify $ editSelectedPlayer f
goto mode
goto :: EditPlayerMode -> Action ()
goto = modify . (progMode.editPlayerStateL.epsMode .~)

View File

@ -29,6 +29,8 @@ import Lens.Micro ((^.))
import Mtlstats.Config
import Mtlstats.Format
import Mtlstats.Helpers.Goalie
import Mtlstats.Helpers.Player
import Mtlstats.Types
import Mtlstats.Util
@ -219,7 +221,7 @@ filteredPlayerReport width label criteria showTotals lineNumbers ps = let
body = map
(\(p, stats) ->
[ CellText $ show (p^.pNumber) ++ " "
, CellText $ p^.pName
, CellText $ playerName p
] ++ statsCells stats)
fps
@ -283,7 +285,7 @@ goalieReport width showTotals lineNumbers goalieData = let
body = map
(\(goalie, stats) ->
[ CellText $ show (goalie^.gNumber) ++ " "
, CellText $ goalie^.gName
, CellText $ goalieName goalie
] ++ rowCells stats)
goalieData
@ -318,7 +320,7 @@ gameGoalieReport width goalieData = let
body = map
(\(goalie, stats) ->
[ CellText $ show (goalie^.gNumber) ++ " "
, CellText $ goalie^.gName
, CellText $ goalieName goalie
, CellText $ show $ stats^.gsMinsPlayed
, CellText $ show $ stats^.gsGoalsAllowed
, CellText $ showFloating $ gsAverage stats

View File

@ -106,6 +106,7 @@ module Mtlstats.Types (
pNumber,
pName,
pPosition,
pRookie,
pYtd,
pLifetime,
-- ** PlayerStats Lenses
@ -115,6 +116,7 @@ module Mtlstats.Types (
-- ** Goalie Lenses
gNumber,
gName,
gRookie,
gYtd,
gLifetime,
-- ** GoalieStats Lenses
@ -399,29 +401,6 @@ data Database = Database
-- ^ Statistics for away games
} deriving (Eq, Show)
instance FromJSON Database where
parseJSON = withObject "Database" $ \v -> Database
<$> v .: "players"
<*> v .: "goalies"
<*> v .: "games"
<*> v .: "home_game_stats"
<*> v .: "away_game_stats"
instance ToJSON Database where
toJSON (Database players goalies games hgs ags) = object
[ "players" .= players
, "goalies" .= goalies
, "games" .= games
, "home_game_stats" .= hgs
, "away_game_stats" .= ags
]
toEncoding (Database players goalies games hgs ags) = pairs $
"players" .= players <>
"goalies" .= goalies <>
"games" .= games <>
"home_game_stats" .= hgs <>
"away_game_stats" .= ags
-- | Represents a (non-goalie) player
data Player = Player
{ _pNumber :: Int
@ -430,35 +409,14 @@ data Player = Player
-- ^ The player's name
, _pPosition :: String
-- ^ The player's position
, _pRookie :: Bool
-- ^ Indicates that the player is a rookie
, _pYtd :: PlayerStats
-- ^ The Player's year-to-date stats
, _pLifetime :: PlayerStats
-- ^ The player's lifetime stats
} deriving (Eq, Show)
instance FromJSON Player where
parseJSON = withObject "Player" $ \v -> Player
<$> v .: "number"
<*> v .: "name"
<*> v .: "position"
<*> v .: "ytd"
<*> v .: "lifetime"
instance ToJSON Player where
toJSON (Player num name pos ytd lt) = object
[ "number" .= num
, "name" .= name
, "position" .= pos
, "ytd" .= ytd
, "lifetime" .= lt
]
toEncoding (Player num name pos ytd lt) = pairs $
"number" .= num <>
"name" .= name <>
"position" .= pos <>
"ytd" .= ytd <>
"lifetime" .= lt
-- | Represents a (non-goalie) player's stats
data PlayerStats = PlayerStats
{ _psGoals :: Int
@ -469,55 +427,20 @@ data PlayerStats = PlayerStats
-- ^ The number of penalty minutes
} deriving (Eq, Show)
instance FromJSON PlayerStats where
parseJSON = withObject "PlayerStats" $ \v -> PlayerStats
<$> v .: "goals"
<*> v .: "assists"
<*> v .: "penalty_mins"
instance ToJSON PlayerStats where
toJSON (PlayerStats g a pm) = object
[ "goals" .= g
, "assists" .= a
, "penalty_mins" .= pm
]
toEncoding (PlayerStats g a pm) = pairs $
"goals" .= g <>
"assists" .= a <>
"penalty_mins" .= pm
-- | Represents a goalie
data Goalie = Goalie
{ _gNumber :: Int
-- ^ The goalie's number
, _gName :: String
-- ^ The goalie's name
, _gRookie :: Bool
-- ^ Indicates that the goalie is a rookie
, _gYtd :: GoalieStats
-- ^ The goalie's year-to-date stats
, _gLifetime :: GoalieStats
-- ^ The goalie's lifetime stats
} deriving (Eq, Show)
instance FromJSON Goalie where
parseJSON = withObject "Goalie" $ \v -> Goalie
<$> v .: "number"
<*> v .: "name"
<*> v .: "ytd"
<*> v .: "lifetime"
instance ToJSON Goalie where
toJSON (Goalie num name ytd lt) = object
[ "number" .= num
, "name" .= name
, "ytd" .= ytd
, "lifetime" .= lt
]
toEncoding (Goalie num name ytd lt) = pairs $
"number" .= num <>
"name" .= name <>
"ytd" .= ytd <>
"lifetime" .= lt
-- | Represents a goalie's stats
data GoalieStats = GoalieStats
{ _gsGames :: Int
@ -536,35 +459,6 @@ data GoalieStats = GoalieStats
-- ^ The number of ties
} deriving (Eq, Show)
instance FromJSON GoalieStats where
parseJSON = withObject "GoalieStats" $ \v -> GoalieStats
<$> v .:? "games" .!= 0
<*> v .:? "mins_played" .!= 0
<*> v .:? "goals_allowed" .!= 0
<*> v .:? "shutouts" .!= 0
<*> v .:? "wins" .!= 0
<*> v .:? "losses" .!= 0
<*> v .:? "ties" .!= 0
instance ToJSON GoalieStats where
toJSON (GoalieStats g m a s w l t) = object
[ "games" .= g
, "mins_played" .= m
, "goals_allowed" .= a
, "shutouts" .= s
, "wins" .= w
, "losses" .= l
, "ties" .= t
]
toEncoding (GoalieStats g m a s w l t) = pairs $
"games" .= g <>
"mins_played" .= m <>
"goals_allowed" .= a <>
"shutouts" .= s <>
"wins" .= w <>
"losses" .= l <>
"ties" .= t
-- | Game statistics
data GameStats = GameStats
{ _gmsWins :: Int
@ -579,29 +473,6 @@ data GameStats = GameStats
-- ^ Goals against the team
} deriving (Eq, Show)
instance FromJSON GameStats where
parseJSON = withObject "GameStats" $ \v -> GameStats
<$> v .: "wins"
<*> v .: "losses"
<*> v .: "overtime"
<*> v .: "goals_for"
<*> v .: "goals_against"
instance ToJSON GameStats where
toJSON (GameStats w l ot gf ga) = object
[ "wins" .= w
, "losses" .= l
, "overtime" .= ot
, "goals_for" .= gf
, "goals_against" .= ga
]
toEncoding (GameStats w l ot gf ga) = pairs $
"wins" .= w <>
"losses" .= l <>
"overtime" .= ot <>
"goals_for" .= gf <>
"goals_against" .= ga
-- | Defines a user prompt
data Prompt = Prompt
{ promptDrawer :: ProgState -> C.Update ()
@ -655,6 +526,147 @@ makeLenses ''Goalie
makeLenses ''GoalieStats
makeLenses ''GameStats
instance FromJSON Database where
parseJSON = withObject "Database" $ \v -> Database
<$> v .:? "players" .!= []
<*> v .:? "goalies" .!= []
<*> v .:? "games" .!= 0
<*> v .:? "home_game_stats" .!= newGameStats
<*> v .:? "away_game_stats" .!= newGameStats
instance ToJSON Database where
toJSON (Database players goalies games hgs ags) = object
[ "players" .= players
, "goalies" .= goalies
, "games" .= games
, "home_game_stats" .= hgs
, "away_game_stats" .= ags
]
toEncoding (Database players goalies games hgs ags) = pairs $
"players" .= players <>
"goalies" .= goalies <>
"games" .= games <>
"home_game_stats" .= hgs <>
"away_game_stats" .= ags
instance FromJSON Player where
parseJSON = withObject "Player" $ \v -> Player
<$> v .: "number"
<*> v .: "name"
<*> v .: "position"
<*> v .:? "rookie" .!= False
<*> v .:? "ytd" .!= newPlayerStats
<*> v .:? "lifetime" .!= newPlayerStats
instance ToJSON Player where
toJSON (Player num name pos rk ytd lt) = object
[ "number" .= num
, "name" .= name
, "position" .= pos
, "rookie" .= rk
, "ytd" .= ytd
, "lifetime" .= lt
]
toEncoding (Player num name pos rk ytd lt) = pairs $
"number" .= num <>
"name" .= name <>
"position" .= pos <>
"rookie" .= rk <>
"ytd" .= ytd <>
"lifetime" .= lt
instance FromJSON PlayerStats where
parseJSON = withObject "PlayerStats" $ \v -> PlayerStats
<$> v .:? "goals" .!= 0
<*> v .:? "assists" .!= 0
<*> v .:? "penalty_mins" .!= 0
instance ToJSON PlayerStats where
toJSON (PlayerStats g a pm) = object
[ "goals" .= g
, "assists" .= a
, "penalty_mins" .= pm
]
toEncoding (PlayerStats g a pm) = pairs $
"goals" .= g <>
"assists" .= a <>
"penalty_mins" .= pm
instance FromJSON Goalie where
parseJSON = withObject "Goalie" $ \v -> Goalie
<$> v .: "number"
<*> v .: "name"
<*> v .:? "rookie" .!= False
<*> v .:? "ytd" .!= newGoalieStats
<*> v .:? "lifetime" .!= newGoalieStats
instance ToJSON Goalie where
toJSON (Goalie num name rk ytd lt) = object
[ "number" .= num
, "name" .= name
, "ytd" .= ytd
, "rookie" .= rk
, "lifetime" .= lt
]
toEncoding (Goalie num name rk ytd lt) = pairs $
"number" .= num <>
"name" .= name <>
"rookie" .= rk <>
"ytd" .= ytd <>
"lifetime" .= lt
instance FromJSON GoalieStats where
parseJSON = withObject "GoalieStats" $ \v -> GoalieStats
<$> v .:? "games" .!= 0
<*> v .:? "mins_played" .!= 0
<*> v .:? "goals_allowed" .!= 0
<*> v .:? "shutouts" .!= 0
<*> v .:? "wins" .!= 0
<*> v .:? "losses" .!= 0
<*> v .:? "ties" .!= 0
instance ToJSON GoalieStats where
toJSON (GoalieStats g m a s w l t) = object
[ "games" .= g
, "mins_played" .= m
, "goals_allowed" .= a
, "shutouts" .= s
, "wins" .= w
, "losses" .= l
, "ties" .= t
]
toEncoding (GoalieStats g m a s w l t) = pairs $
"games" .= g <>
"mins_played" .= m <>
"goals_allowed" .= a <>
"shutouts" .= s <>
"wins" .= w <>
"losses" .= l <>
"ties" .= t
instance FromJSON GameStats where
parseJSON = withObject "GameStats" $ \v -> GameStats
<$> v .: "wins"
<*> v .: "losses"
<*> v .: "overtime"
<*> v .: "goals_for"
<*> v .: "goals_against"
instance ToJSON GameStats where
toJSON (GameStats w l ot gf ga) = object
[ "wins" .= w
, "losses" .= l
, "overtime" .= ot
, "goals_for" .= gf
, "goals_against" .= ga
]
toEncoding (GameStats w l ot gf ga) = pairs $
"wins" .= w <>
"losses" .= l <>
"overtime" .= ot <>
"goals_for" .= gf <>
"goals_against" .= ga
gameStateL :: Lens' ProgMode GameState
gameStateL = lens
(\case
@ -782,6 +794,7 @@ newPlayer num name pos = Player
{ _pNumber = num
, _pName = name
, _pPosition = pos
, _pRookie = True
, _pYtd = newPlayerStats
, _pLifetime = newPlayerStats
}
@ -804,6 +817,7 @@ newGoalie
newGoalie num name = Goalie
{ _gNumber = num
, _gName = name
, _gRookie = True
, _gYtd = newGoalieStats
, _gLifetime = newGoalieStats
}

View File

@ -53,7 +53,9 @@ spec = describe "Mtlstats.Actions" $ do
createGoalieSpec
editSpec
editPlayerSpec
editSelectedPlayerSpec
editGoalieSpec
editSelectedGoalieSpec
addPlayerSpec
addGoalieSpec
resetCreatePlayerStateSpec
@ -209,12 +211,64 @@ editPlayerSpec = describe "editPlayer" $
s = editPlayer newProgState
in show (s^.progMode) `shouldBe` "EditPlayer"
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"
editGoalieSpec :: Spec
editGoalieSpec = describe "editGoalie" $
it "should change the mode appropriately" $ let
s = editGoalie newProgState
in show (s^.progMode) `shouldBe` "EditGoalie"
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 )
, ( "goalie 0", changeGoalie $ Just 0, changed0 )
, ( "goalie 1", changeGoalie $ Just 1, changed1 )
, ( "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"
addPlayerSpec :: Spec
addPlayerSpec = describe "addPlayer" $ do
let

View File

@ -22,18 +22,20 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Helpers.GoalieSpec (spec) where
import Lens.Micro ((&), (.~), (%~))
import Test.Hspec (Spec, describe, it, shouldBe)
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Helpers.Goalie
import Mtlstats.Types
spec :: Spec
spec = describe "Goalie"
spec = describe "Goalie" $ do
goalieDetailsSpec
goalieNameSpec
goalieDetailsSpec :: Spec
goalieDetailsSpec = describe "goalieDetails" $ let
input = newGoalie 1 "Joe"
& gRookie .~ True
& gYtd
%~ ( gsGames .~ 2 )
. ( gsMinsPlayed .~ 3 )
@ -53,7 +55,7 @@ goalieDetailsSpec = describe "goalieDetails" $ let
expected = unlines
[ "Number: 1"
, " Name: Joe"
, " Name: Joe*"
, ""
, " YTD Lifetime"
, " Games played 2 9"
@ -67,3 +69,17 @@ goalieDetailsSpec = describe "goalieDetails" $ let
in it "should format the output correctly" $
goalieDetails input `shouldBe` expected
goalieNameSpec :: Spec
goalieNameSpec = describe "goalieName" $ mapM_
(\(label, g, expected) -> context label $
it ("should be " ++ expected) $
goalieName g `shouldBe` expected)
-- label, goalie, expected
[ ( "rookie", goalie True, "foo*" )
, ( "non-rookie", goalie False, "foo" )
]
where
goalie r = newGoalie 1 "foo" & gRookie .~ r

View File

@ -22,20 +22,22 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Helpers.PlayerSpec (spec) where
import Lens.Micro ((&), (.~))
import Test.Hspec (Spec, describe, it, shouldBe)
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Helpers.Player
import Mtlstats.Types
spec :: Spec
spec = describe "Player"
spec = describe "Player" $ do
playerDetailsSpec
playerNameSpec
playerDetailsSpec :: Spec
playerDetailsSpec = describe "playerDetails" $
it "should give a detailed description" $ let
p = newPlayer 1 "Joe" "centre"
& pRookie .~ True
& pYtd .~ PlayerStats
{ _psGoals = 2
, _psAssists = 3
@ -49,7 +51,7 @@ playerDetailsSpec = describe "playerDetails" $
expected = unlines
[ " Number: 1"
, " Name: Joe"
, " Name: Joe*"
, "Position: centre"
, ""
, " YTD Lifetime"
@ -59,3 +61,19 @@ playerDetailsSpec = describe "playerDetails" $
]
in playerDetails p `shouldBe` expected
playerNameSpec :: Spec
playerNameSpec = describe "playerName" $ mapM_
(\(label, p, expected) -> context label $
it ("should be " ++ expected) $
playerName p `shouldBe` expected)
-- label, player, expected
[ ( "rookie", rookie, "foo*" )
, ( "non-rookie", nonRookie, "foo" )
]
where
rookie = player True
nonRookie = player False
player r = newPlayer 1 "foo" "centre" & pRookie .~ r

View File

@ -36,7 +36,7 @@ import Data.Aeson.Types (Value (Object))
import qualified Data.HashMap.Strict as HM
import Data.Ratio ((%))
import Lens.Micro (Lens', (&), (^.), (.~), (?~))
import System.Random (randomRIO)
import System.Random (randomIO, randomRIO)
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Config
@ -271,6 +271,7 @@ lensSpec lens getters setters = do
player :: Player
player = newPlayer 1 "Joe" "centre"
& pRookie .~ False
& pYtd .~ playerStats 1
& pLifetime .~ playerStats 2
@ -279,6 +280,7 @@ playerJSON = Object $ HM.fromList
[ ( "number", toJSON (1 :: Int) )
, ( "name", toJSON ("Joe" :: String) )
, ( "position", toJSON ("centre" :: String) )
, ( "rookie", toJSON False )
, ( "ytd", playerStatsJSON 1 )
, ( "lifetime", playerStatsJSON 2 )
]
@ -298,6 +300,7 @@ playerStatsJSON n = Object $ HM.fromList
goalie :: Goalie
goalie = newGoalie 1 "Joe"
& gRookie .~ False
& gYtd .~ goalieStats 1
& gLifetime .~ goalieStats 2
@ -305,6 +308,7 @@ goalieJSON :: Value
goalieJSON = Object $ HM.fromList
[ ( "number", toJSON (1 :: Int) )
, ( "name", toJSON ("Joe" :: String ) )
, ( "rookie", toJSON False )
, ( "ytd", goalieStatsJSON 1 )
, ( "lifetime", goalieStatsJSON 2 )
]
@ -843,6 +847,7 @@ makePlayer = Player
<$> makeNum
<*> makeName
<*> makeName
<*> makeBool
<*> makePlayerStats
<*> makePlayerStats
@ -851,6 +856,7 @@ makeGoalie :: IO Goalie
makeGoalie = Goalie
<$> makeNum
<*> makeName
<*> makeBool
<*> makeGoalieStats
<*> makeGoalieStats
@ -875,6 +881,9 @@ makeGoalieStats = GoalieStats
makeNum :: IO Int
makeNum = randomRIO (1, 10)
makeBool :: IO Bool
makeBool = randomIO
makeName :: IO String
makeName = replicateM 10 $ randomRIO ('A', 'Z')