be pedantic
This commit is contained in:
parent
9288d885cd
commit
c99a39b2b9
|
@ -33,6 +33,10 @@ dependencies:
|
||||||
- bytestring
|
- bytestring
|
||||||
- microlens
|
- microlens
|
||||||
|
|
||||||
|
ghc-options:
|
||||||
|
- -Wall
|
||||||
|
- -Werror
|
||||||
|
|
||||||
library:
|
library:
|
||||||
source-dirs: src
|
source-dirs: src
|
||||||
|
|
||||||
|
|
|
@ -54,10 +54,10 @@ recordGoalieStats s = fromMaybe s $ do
|
||||||
then 1
|
then 1
|
||||||
else 0
|
else 0
|
||||||
|
|
||||||
bumpStats gs = gs
|
bumpStats
|
||||||
& gsGames +~ bumpVal
|
= (gsGames +~ bumpVal)
|
||||||
& gsMinsPlayed +~ mins
|
. (gsMinsPlayed +~ mins)
|
||||||
& gsGoalsAllowed +~ goals
|
. (gsGoalsAllowed +~ goals)
|
||||||
|
|
||||||
tryFinish = if mins >= gameLength
|
tryFinish = if mins >= gameLength
|
||||||
then finishGoalieEntry
|
then finishGoalieEntry
|
||||||
|
@ -91,18 +91,18 @@ setGameGoalie gid s = fromMaybe s $ do
|
||||||
l = if lost then 1 else 0
|
l = if lost then 1 else 0
|
||||||
t = if tied then 1 else 0
|
t = if tied then 1 else 0
|
||||||
|
|
||||||
updateStats gs = gs
|
updateStats
|
||||||
& gsWins +~ w
|
= (gsWins +~ w)
|
||||||
& gsLosses +~ l
|
. (gsLosses +~ l)
|
||||||
& gsTies +~ t
|
. (gsTies +~ t)
|
||||||
|
|
||||||
updateGoalie g = g
|
updateGoalie
|
||||||
& gYtd %~ updateStats
|
= (gYtd %~ updateStats)
|
||||||
& gLifetime %~ updateStats
|
. (gLifetime %~ updateStats)
|
||||||
|
|
||||||
updateGameState gs = gs
|
updateGameState
|
||||||
& gameGoalieStats %~ updateMap gid newGoalieStats updateStats
|
= (gameGoalieStats %~ updateMap gid newGoalieStats updateStats)
|
||||||
& gameGoalieAssigned .~ True
|
. (gameGoalieAssigned .~ True)
|
||||||
|
|
||||||
Just $ s
|
Just $ s
|
||||||
& database.dbGoalies %~ modifyNth gid updateGoalie
|
& database.dbGoalies %~ modifyNth gid updateGoalie
|
||||||
|
|
|
@ -162,9 +162,9 @@ selectPrompt params = Prompt
|
||||||
n = pred $ fromInteger rawK
|
n = pred $ fromInteger rawK
|
||||||
results = spSearch params sStr db
|
results = spSearch params sStr db
|
||||||
when (n < maxFunKeys) $
|
when (n < maxFunKeys) $
|
||||||
whenJust (nth n results) $ \(n, _) -> do
|
whenJust (nth n results) $ \(sel, _) -> do
|
||||||
modify $ inputBuffer .~ ""
|
modify $ inputBuffer .~ ""
|
||||||
spCallback params $ Just n
|
spCallback params $ Just sel
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
|
@ -111,10 +111,10 @@ lifetimeStatsReport width s = playerReport width "LIFETIME" $
|
||||||
|
|
||||||
gameDate :: GameState -> String
|
gameDate :: GameState -> String
|
||||||
gameDate gs = fromMaybe "" $ do
|
gameDate gs = fromMaybe "" $ do
|
||||||
year <- show <$> gs^.gameYear
|
y <- show <$> gs^.gameYear
|
||||||
month <- month <$> gs^.gameMonth
|
m <- month <$> gs^.gameMonth
|
||||||
day <- padNum 2 <$> gs^.gameDay
|
d <- padNum 2 <$> gs^.gameDay
|
||||||
Just $ month ++ " " ++ day ++ " " ++ year
|
Just $ m ++ " " ++ d ++ " " ++ y
|
||||||
|
|
||||||
playerReport :: Int -> String -> [(Player, PlayerStats)] -> [String]
|
playerReport :: Int -> String -> [(Player, PlayerStats)] -> [String]
|
||||||
playerReport width label ps = let
|
playerReport width label ps = let
|
||||||
|
|
|
@ -828,9 +828,8 @@ playerSearch
|
||||||
-> [(Int, Player)]
|
-> [(Int, Player)]
|
||||||
-- ^ The matching players with their index numbers
|
-- ^ The matching players with their index numbers
|
||||||
playerSearch sStr =
|
playerSearch sStr =
|
||||||
filter (match sStr) .
|
filter match . zip [0..]
|
||||||
zip [0..]
|
where match (_, p) = sStr `isInfixOf` (p^.pName)
|
||||||
where match sStr (_, p) = sStr `isInfixOf` (p^.pName)
|
|
||||||
|
|
||||||
-- | Searches for a player by exact match on name
|
-- | Searches for a player by exact match on name
|
||||||
playerSearchExact
|
playerSearchExact
|
||||||
|
@ -841,10 +840,8 @@ playerSearchExact
|
||||||
-> Maybe (Int, Player)
|
-> Maybe (Int, Player)
|
||||||
-- ^ The player's index and value
|
-- ^ The player's index and value
|
||||||
playerSearchExact sStr =
|
playerSearchExact sStr =
|
||||||
listToMaybe .
|
listToMaybe . filter match . zip [0..]
|
||||||
filter (match sStr) .
|
where match (_, p) = p^.pName == sStr
|
||||||
zip [0..]
|
|
||||||
where match sStr (_, p) = p^.pName == sStr
|
|
||||||
|
|
||||||
-- | Modifies a player with a given name
|
-- | Modifies a player with a given name
|
||||||
modifyPlayer
|
modifyPlayer
|
||||||
|
|
|
@ -81,13 +81,13 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
|
||||||
& progMode.gameStateL .~ gameState n mins goals
|
& progMode.gameStateL .~ gameState n mins goals
|
||||||
|
|
||||||
in mapM_
|
in mapM_
|
||||||
(\(name, gid, mins, goals, joeData, bobData, reset) -> let
|
(\(setName, setGid, mins, goals, joeData, bobData, reset) -> let
|
||||||
s = recordGoalieStats $ progState gid mins goals
|
s = recordGoalieStats $ progState setGid mins goals
|
||||||
in context name $ do
|
in context setName $ do
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
(\( name
|
(\( chkName
|
||||||
, gid
|
, chkGid
|
||||||
, ( gGames
|
, ( gGames
|
||||||
, gMins
|
, gMins
|
||||||
, gGoals
|
, gGoals
|
||||||
|
@ -98,11 +98,11 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
|
||||||
, ltMins
|
, ltMins
|
||||||
, ltGoals
|
, ltGoals
|
||||||
)
|
)
|
||||||
) -> context name $ do
|
) -> context chkName $ do
|
||||||
let
|
let
|
||||||
gs = s^.progMode.gameStateL.gameGoalieStats
|
gs = s^.progMode.gameStateL.gameGoalieStats
|
||||||
game = M.findWithDefault newGoalieStats gid gs
|
game = M.findWithDefault newGoalieStats chkGid gs
|
||||||
goalie = fromJust $ nth gid $ s^.database.dbGoalies
|
goalie = fromJust $ nth chkGid $ s^.database.dbGoalies
|
||||||
ytd = goalie^.gYtd
|
ytd = goalie^.gYtd
|
||||||
lt = goalie^.gLifetime
|
lt = goalie^.gLifetime
|
||||||
|
|
||||||
|
@ -120,7 +120,7 @@ recordGoalieStatsSpec = describe "recordGoalieStats" $ let
|
||||||
]
|
]
|
||||||
|
|
||||||
context "selected goalie" $ let
|
context "selected goalie" $ let
|
||||||
expected = if reset then Nothing else gid
|
expected = if reset then Nothing else setGid
|
||||||
in it ("should be " ++ show expected) $
|
in it ("should be " ++ show expected) $
|
||||||
(s^.progMode.gameStateL.gameSelectedGoalie) `shouldBe` expected
|
(s^.progMode.gameStateL.gameSelectedGoalie) `shouldBe` expected
|
||||||
|
|
||||||
|
@ -211,16 +211,16 @@ setGameGoalieSpec = describe "setGameGoalie" $ let
|
||||||
tiedGame = gameState 0 1 True
|
tiedGame = gameState 0 1 True
|
||||||
|
|
||||||
in mapM_
|
in mapM_
|
||||||
(\(label, gameState, gid, bobData, joeData) -> context label $ let
|
(\(setLabel, gs, setGid, bobData, joeData) -> context setLabel $ let
|
||||||
|
|
||||||
progState = newProgState
|
progState = newProgState
|
||||||
& database.dbGoalies .~ [bob, joe]
|
& database.dbGoalies .~ [bob, joe]
|
||||||
& progMode.gameStateL .~ gameState
|
& progMode.gameStateL .~ gs
|
||||||
& setGameGoalie gid
|
& setGameGoalie setGid
|
||||||
|
|
||||||
in mapM_
|
in mapM_
|
||||||
(\( label
|
(\( chkLabel
|
||||||
, gid
|
, chkGid
|
||||||
, ( gWins
|
, ( gWins
|
||||||
, gLosses
|
, gLosses
|
||||||
, gTies
|
, gTies
|
||||||
|
@ -231,16 +231,16 @@ setGameGoalieSpec = describe "setGameGoalie" $ let
|
||||||
, ltLosses
|
, ltLosses
|
||||||
, ltTies
|
, ltTies
|
||||||
)
|
)
|
||||||
) -> context label $ do
|
) -> context chkLabel $ do
|
||||||
let
|
let
|
||||||
goalie = (progState^.database.dbGoalies) !! gid
|
goalie = (progState^.database.dbGoalies) !! chkGid
|
||||||
gameStats = progState^.progMode.gameStateL.gameGoalieStats
|
gameStats = progState^.progMode.gameStateL.gameGoalieStats
|
||||||
game = M.findWithDefault newGoalieStats gid gameStats
|
game = M.findWithDefault newGoalieStats chkGid gameStats
|
||||||
ytd = goalie^.gYtd
|
ytd = goalie^.gYtd
|
||||||
lifetime = goalie^.gLifetime
|
lifetime = goalie^.gLifetime
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
(\(label, expected, actual) -> context label $
|
(\(label', expected, actual) -> context label' $
|
||||||
expected `TS.compareTest` actual)
|
expected `TS.compareTest` actual)
|
||||||
[ ( "game stats", game, goalieStats gWins gLosses gTies )
|
[ ( "game stats", game, goalieStats gWins gLosses gTies )
|
||||||
, ( "YTD stats", ytd, goalieStats ytdWins ytdLosses ytdTies )
|
, ( "YTD stats", ytd, goalieStats ytdWins ytdLosses ytdTies )
|
||||||
|
|
|
@ -327,20 +327,20 @@ awardGoalSpec = describe "awardGoal" $ do
|
||||||
& database .~ db
|
& database .~ db
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
(\(pName, pid, ytd, lt, game) ->
|
(\(name, pid, ytd, lt, game) ->
|
||||||
context pName $ do
|
context name $ do
|
||||||
let
|
let
|
||||||
ps' = awardGoal pid ps
|
ps' = awardGoal pid ps
|
||||||
player = (ps'^.database.dbPlayers) !! pid
|
player = (ps'^.database.dbPlayers) !! pid
|
||||||
gStats = (ps'^.progMode.gameStateL.gamePlayerStats) M.! pid
|
gStats = (ps'^.progMode.gameStateL.gamePlayerStats) M.! pid
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s year-to-date goals") $
|
it ("should increment " ++ name ++ "'s year-to-date goals") $
|
||||||
player^.pYtd.psGoals `shouldBe` ytd
|
player^.pYtd.psGoals `shouldBe` ytd
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s lifetime goals") $
|
it ("should increment " ++ name ++ "'s lifetime goals") $
|
||||||
player^.pLifetime.psGoals `shouldBe` lt
|
player^.pLifetime.psGoals `shouldBe` lt
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s game goals") $
|
it ("should increment " ++ name ++ "'s game goals") $
|
||||||
gStats^.psGoals `shouldBe` game)
|
gStats^.psGoals `shouldBe` game)
|
||||||
-- player name, player id, ytd goals, lifetime goals, game goals
|
-- player name, player id, ytd goals, lifetime goals, game goals
|
||||||
[ ( "Joe", 0, 2, 3, 2 )
|
[ ( "Joe", 0, 2, 3, 2 )
|
||||||
|
@ -377,20 +377,20 @@ awardAssistSpec = describe "awardAssist" $ do
|
||||||
& database.dbPlayers .~ [joe, bob]
|
& database.dbPlayers .~ [joe, bob]
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
(\(pName, pid, ytd, lt, game) ->
|
(\(name, pid, ytd, lt, game) ->
|
||||||
context pName $ do
|
context name $ do
|
||||||
let
|
let
|
||||||
ps' = awardAssist pid ps
|
ps' = awardAssist pid ps
|
||||||
player = (ps'^.database.dbPlayers) !! pid
|
player = (ps'^.database.dbPlayers) !! pid
|
||||||
gStats = (ps'^.progMode.gameStateL.gamePlayerStats) M.! pid
|
gStats = (ps'^.progMode.gameStateL.gamePlayerStats) M.! pid
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s year-to-date assists") $
|
it ("should increment " ++ name ++ "'s year-to-date assists") $
|
||||||
player^.pYtd.psAssists `shouldBe` ytd
|
player^.pYtd.psAssists `shouldBe` ytd
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s lifetime assists") $
|
it ("should increment " ++ name ++ "'s lifetime assists") $
|
||||||
player^.pLifetime.psAssists `shouldBe` lt
|
player^.pLifetime.psAssists `shouldBe` lt
|
||||||
|
|
||||||
it ("should increment " ++ pName ++ "'s game assists") $
|
it ("should increment " ++ name ++ "'s game assists") $
|
||||||
gStats^.psAssists `shouldBe` game)
|
gStats^.psAssists `shouldBe` game)
|
||||||
-- player name, player id, ytd assists, lifetime assists, game assists
|
-- player name, player id, ytd assists, lifetime assists, game assists
|
||||||
[ ( "Joe", 0, 2, 3, 2 )
|
[ ( "Joe", 0, 2, 3, 2 )
|
||||||
|
|
|
@ -589,22 +589,22 @@ playerSearchExactSpec = describe "playerSearchExact" $ mapM_
|
||||||
|
|
||||||
modifyPlayerSpec :: Spec
|
modifyPlayerSpec :: Spec
|
||||||
modifyPlayerSpec = describe "modifyPlayer" $ mapM_
|
modifyPlayerSpec = describe "modifyPlayer" $ mapM_
|
||||||
(\(pName, j, b, s) -> let
|
(\(name, j, b, s) -> let
|
||||||
modifier = pLifetime.psGoals .~ 1
|
modifier = pLifetime.psGoals .~ 1
|
||||||
players = modifyPlayer modifier pName [joe, bob, steve]
|
players = modifyPlayer modifier name [joe, bob, steve]
|
||||||
in context ("modify " ++ pName) $ do
|
in context ("modify " ++ name) $ do
|
||||||
|
|
||||||
context "Joe's lifetime goals" $
|
context "Joe's lifetime goals" $
|
||||||
it ("should be " ++ show j) $
|
it ("should be " ++ show j) $
|
||||||
head players ^. pLifetime.psGoals `shouldBe` j
|
head players^.pLifetime.psGoals `shouldBe` j
|
||||||
|
|
||||||
context "Bob's lifetime goals" $
|
context "Bob's lifetime goals" $
|
||||||
it ("should be " ++ show b) $
|
it ("should be " ++ show b) $
|
||||||
(players !! 1) ^. pLifetime.psGoals `shouldBe` b
|
(players !! 1)^.pLifetime.psGoals `shouldBe` b
|
||||||
|
|
||||||
context "Steve's lifetime goals" $
|
context "Steve's lifetime goals" $
|
||||||
it ("should be " ++ show s) $
|
it ("should be " ++ show s) $
|
||||||
last players ^. pLifetime.psGoals `shouldBe` s)
|
last players^.pLifetime.psGoals `shouldBe` s)
|
||||||
-- player name, Joe's goals, Bob's goals, Steve's goals
|
-- player name, Joe's goals, Bob's goals, Steve's goals
|
||||||
[ ( "Joe", 1, 0, 0 )
|
[ ( "Joe", 1, 0, 0 )
|
||||||
, ( "Bob", 0, 1, 0 )
|
, ( "Bob", 0, 1, 0 )
|
||||||
|
@ -621,7 +621,7 @@ playerDetailsSpec :: Spec
|
||||||
playerDetailsSpec = describe "playerDetails" $
|
playerDetailsSpec = describe "playerDetails" $
|
||||||
it "should give a detailed description" $ let
|
it "should give a detailed description" $ let
|
||||||
|
|
||||||
player = newPlayer 1 "Joe" "centre"
|
p = newPlayer 1 "Joe" "centre"
|
||||||
& pYtd .~ PlayerStats
|
& pYtd .~ PlayerStats
|
||||||
{ _psGoals = 2
|
{ _psGoals = 2
|
||||||
, _psAssists = 3
|
, _psAssists = 3
|
||||||
|
@ -645,26 +645,26 @@ playerDetailsSpec = describe "playerDetails" $
|
||||||
, "Lifetime penalty mins: 7"
|
, "Lifetime penalty mins: 7"
|
||||||
]
|
]
|
||||||
|
|
||||||
in playerDetails player `shouldBe` expected
|
in playerDetails p `shouldBe` expected
|
||||||
|
|
||||||
playerIsActiveSpec :: Spec
|
playerIsActiveSpec :: Spec
|
||||||
playerIsActiveSpec = describe "playerIsActive" $ do
|
playerIsActiveSpec = describe "playerIsActive" $ do
|
||||||
let
|
let
|
||||||
pState = newPlayerStats
|
pStats = newPlayerStats
|
||||||
& psGoals .~ 10
|
& psGoals .~ 10
|
||||||
& psAssists .~ 11
|
& psAssists .~ 11
|
||||||
& psPMin .~ 12
|
& psPMin .~ 12
|
||||||
player = newPlayer 1 "Joe" "centre" & pLifetime .~ pState
|
p = newPlayer 1 "Joe" "centre" & pLifetime .~ pStats
|
||||||
|
|
||||||
mapM_
|
mapM_
|
||||||
(\(label, player', expected) -> context label $
|
(\(label, p', expected) -> context label $
|
||||||
it ("should be " ++ show expected) $
|
it ("should be " ++ show expected) $
|
||||||
playerIsActive player' `shouldBe` expected)
|
playerIsActive p' `shouldBe` expected)
|
||||||
-- label, player, expected
|
-- label, player, expected
|
||||||
[ ( "not active", player, False )
|
[ ( "not active", p, False )
|
||||||
, ( "has goal", player & pYtd.psGoals .~ 1, True )
|
, ( "has goal", p & pYtd.psGoals .~ 1, True )
|
||||||
, ( "has assist", player & pYtd.psAssists .~ 1, True )
|
, ( "has assist", p & pYtd.psAssists .~ 1, True )
|
||||||
, ( "has penalty minute", player & pYtd.psPMin .~ 1, True )
|
, ( "has penalty minute", p & pYtd.psPMin .~ 1, True )
|
||||||
]
|
]
|
||||||
|
|
||||||
psPointsSpec :: Spec
|
psPointsSpec :: Spec
|
||||||
|
|
|
@ -49,18 +49,19 @@ nthSpec = describe "nth" $ mapM_
|
||||||
|
|
||||||
modifyNthSpec :: Spec
|
modifyNthSpec :: Spec
|
||||||
modifyNthSpec = describe "modifyNth" $ do
|
modifyNthSpec = describe "modifyNth" $ do
|
||||||
|
let list = [1, 2, 3] :: [Int]
|
||||||
|
|
||||||
context "in bounds" $
|
context "in bounds" $
|
||||||
it "should modify the value" $
|
it "should modify the value" $
|
||||||
modifyNth 1 succ [1, 2, 3] `shouldBe` [1, 3, 3]
|
modifyNth 1 succ list `shouldBe` [1, 3, 3]
|
||||||
|
|
||||||
context "out of bounds" $
|
context "out of bounds" $
|
||||||
it "should not modify the value" $
|
it "should not modify the value" $
|
||||||
modifyNth 3 succ [1, 2, 3] `shouldBe` [1, 2, 3]
|
modifyNth 3 succ list `shouldBe` [1, 2, 3]
|
||||||
|
|
||||||
context "negative index" $
|
context "negative index" $
|
||||||
it "should not modify the value" $
|
it "should not modify the value" $
|
||||||
modifyNth (-1) succ [1, 2, 3] `shouldBe` [1, 2, 3]
|
modifyNth (-1) succ list `shouldBe` [1, 2, 3]
|
||||||
|
|
||||||
updateMapSpec :: Spec
|
updateMapSpec :: Spec
|
||||||
updateMapSpec = describe "updateMap" $ do
|
updateMapSpec = describe "updateMap" $ do
|
||||||
|
@ -68,7 +69,7 @@ updateMapSpec = describe "updateMap" $ do
|
||||||
input = M.fromList [(1, 2), (3, 5)]
|
input = M.fromList [(1, 2), (3, 5)]
|
||||||
|
|
||||||
context "key found" $ let
|
context "key found" $ let
|
||||||
expected = M.fromList [(1, 3), (3, 5)]
|
expected = M.fromList [(1, 3), (3, 5)] :: M.Map Int Int
|
||||||
in it "should update the value" $
|
in it "should update the value" $
|
||||||
updateMap 1 10 succ input `shouldBe` expected
|
updateMap 1 10 succ input `shouldBe` expected
|
||||||
|
|
||||||
|
@ -79,7 +80,7 @@ updateMapSpec = describe "updateMap" $ do
|
||||||
|
|
||||||
sliceSpec :: Spec
|
sliceSpec :: Spec
|
||||||
sliceSpec = describe "slice" $ do
|
sliceSpec = describe "slice" $ do
|
||||||
let list = [2, 4, 6, 8]
|
let list = [2, 4, 6, 8] :: [Int]
|
||||||
|
|
||||||
context "sublist" $
|
context "sublist" $
|
||||||
it "should return the sublist" $
|
it "should return the sublist" $
|
||||||
|
|
Loading…
Reference in New Issue
Block a user