mtlstats/test/TypesSpec.hs

317 lines
7.7 KiB
Haskell
Raw Normal View History

2019-08-20 11:31:03 -04:00
{-
mtlstats
Copyright (C) 2019 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/>.
-}
2019-08-10 10:01:36 -04:00
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
2019-08-09 11:06:13 -04:00
module TypesSpec (spec) where
2019-08-10 10:01:36 -04:00
import Data.Aeson (decode, encode)
import Data.ByteString.Lazy (ByteString)
2019-08-22 13:05:25 -04:00
import Lens.Micro ((&), (^.), (.~), (?~))
2019-08-09 11:06:13 -04:00
import Test.Hspec (Spec, context, describe, it, shouldBe)
2019-08-10 10:01:36 -04:00
import Text.RawString.QQ (r)
2019-08-09 11:06:13 -04:00
import Mtlstats.Types
2019-08-21 00:21:22 -04:00
import qualified Types.MenuSpec as Menu
2019-08-09 11:06:13 -04:00
spec :: Spec
2019-08-10 10:01:36 -04:00
spec = describe "Mtlstats.Types" $ do
playerSpec
pPointsSpec
2019-08-11 10:24:39 -04:00
goalieSpec
2019-08-16 11:49:04 -04:00
databaseSpec
2019-08-22 13:05:25 -04:00
gameTypeLSpec
otherTeamLSpec
2019-08-22 14:19:43 -04:00
homeScoreLSpec
2019-08-22 14:33:39 -04:00
awayScoreLSpec
teamScoreSpec
2019-08-21 00:21:22 -04:00
Menu.spec
2019-08-09 11:06:13 -04:00
playerSpec :: Spec
playerSpec = describe "Player" $ do
describe "decode" $
it "should decode" $
decode playerJSON `shouldBe` Just player
describe "encode" $
it "should encode" $
decode (encode player) `shouldBe` Just player
2019-08-10 10:01:36 -04:00
pPointsSpec :: Spec
2019-08-09 11:06:13 -04:00
pPointsSpec = describe "pPoints" $ mapM_
(\(goals, assists, points) -> let
desc = "goals: " ++ show goals ++
", assists: " ++ show assists
stats = newPlayerStats &
psGoals .~ goals &
psAssists .~ assists
in context desc $
it ("should be " ++ show points) $
pPoints stats `shouldBe` points)
-- goals, assists, points
[ ( 0, 0, 0 )
, ( 1, 0, 1 )
, ( 0, 1, 1 )
, ( 2, 3, 5 )
]
2019-08-10 10:01:36 -04:00
2019-08-11 10:24:39 -04:00
goalieSpec :: Spec
goalieSpec = describe "Goalie" $ do
describe "decode" $
it "should decode" $
decode goalieJSON `shouldBe` Just goalie
describe "encode" $
it "should encode" $
decode (encode goalie) `shouldBe` Just goalie
2019-08-16 11:49:04 -04:00
databaseSpec :: Spec
databaseSpec = describe "Database" $ do
describe "decode" $
it "should decode" $
decode dbJSON `shouldBe` Just db
describe "encode" $
it "should encode" $
decode (encode db) `shouldBe` Just db
2019-08-22 13:05:25 -04:00
gameTypeLSpec :: Spec
gameTypeLSpec = describe "gameTypeL" $ do
context "getter" $ do
context "unexpected mode" $
2019-08-23 10:20:06 -04:00
it "should return Nothing" $
2019-08-22 13:05:25 -04:00
MainMenu ^. gameTypeL `shouldBe` Nothing
mapM_
(\t -> context (show t) $
it ("should return " ++ show t) $ let
gs = newGameState & gameType ?~ t
m = NewGame gs
in m ^. gameTypeL `shouldBe` Just t)
[HomeGame, AwayGame]
context "setter" $ do
context "unexpected mode" $
mapM_
(\t -> context (show t) $
it ("should set to " ++ show t) $ let
m = MainMenu & gameTypeL ?~ t
in m ^. gameTypeL `shouldBe` Just t)
[HomeGame, AwayGame]
context "expected mode" $
mapM_
(\t -> context (show t) $
it ("should set to " ++ show t) $ let
m = NewGame newGameState & gameTypeL ?~ t
in m ^. gameTypeL `shouldBe` Just t)
[HomeGame, AwayGame]
otherTeamLSpec :: Spec
otherTeamLSpec = describe "otherTeamL" $ do
context "getter" $ do
context "unexpected mode" $
it "should return an empty string" $
MainMenu ^. otherTeamL `shouldBe` ""
context "expected mode" $
it "should return \"foo\"" $ let
m = NewGame $ newGameState & otherTeam .~ "foo"
in m ^. otherTeamL `shouldBe` "foo"
context "setter" $ do
context "unexpected mode" $
it "should set the value" $ let
m = MainMenu & otherTeamL .~ "foo"
in m ^. otherTeamL `shouldBe` "foo"
context "expected mode" $
it "should set the value" $ let
m = NewGame newGameState & otherTeamL .~ "foo"
in m ^. otherTeamL `shouldBe` "foo"
2019-08-25 09:25:34 -04:00
homeScoreLSpec :: Spec
2019-08-22 14:19:43 -04:00
homeScoreLSpec = describe "homeScoreL" $ do
context "getter" $ do
context "unexpected mode" $
it "should return Nothing" $
MainMenu ^. homeScoreL `shouldBe` Nothing
context "expected mode" $
it "should return 0" $ let
gs = newGameState & homeScore ?~ 0
m = NewGame gs
in m ^. homeScoreL `shouldBe` Just 0
context "setter" $ do
context "unexpected mode" $
2019-08-22 14:33:39 -04:00
it "should set home score" $ let
2019-08-22 14:19:43 -04:00
m = MainMenu & homeScoreL ?~ 0
in m ^. homeScoreL `shouldBe` Just 0
context "expected mode" $
2019-08-22 14:33:39 -04:00
it "should set home score" $ let
2019-08-22 14:19:43 -04:00
m = NewGame newGameState & homeScoreL ?~ 0
in m ^. homeScoreL `shouldBe` Just 0
2019-08-22 14:33:39 -04:00
awayScoreLSpec :: Spec
awayScoreLSpec = describe "awayScoreL" $ do
context "getter" $ do
context "unexpected mode" $
it "should return Nothing" $
MainMenu ^. awayScoreL `shouldBe` Nothing
context "expected mode" $
it "should return 0" $ let
gs = newGameState & awayScore ?~ 0
m = NewGame gs
in m ^. awayScoreL `shouldBe` Just 0
context "setter" $ do
context "unexpected mode" $
it "should set the away score" $ let
m = MainMenu & awayScoreL ?~ 0
in m ^. awayScoreL `shouldBe` Just 0
context "expected mode" $
it "should set the away score" $ let
m = NewGame newGameState & awayScoreL ?~ 0
in m ^. awayScoreL `shouldBe` Just 0
teamScoreSpec :: Spec
teamScoreSpec = describe "teamScore" $ do
let
m t = NewGame $ newGameState
& gameType ?~ t
& homeScore ?~ 1
& awayScore ?~ 2
s t = newProgState
& progMode .~ m t
context "unexpected state" $
it "should return Nothing" $
teamScore newProgState `shouldBe` Nothing
context "HomeGame" $
it "should return 1" $
teamScore (s HomeGame) `shouldBe` Just 1
context "AwayGame" $
it "should return 2" $
teamScore (s AwayGame) `shouldBe` Just 2
2019-08-10 10:01:36 -04:00
player :: Player
player = newPlayer 1 "Joe" "centre"
& pYtd . psGoals .~ 2
& pYtd . psAssists .~ 3
& pYtd . psPMin .~ 4
& pLifetime . psGoals .~ 5
& pLifetime . psAssists .~ 6
& pLifetime . psPMin .~ 7
2019-08-11 10:24:39 -04:00
goalie :: Goalie
goalie = newGoalie 1 "Joe"
& gYtd . gsGames .~ 2
& gYtd . gsMinsPlayed .~ 3
& gYtd . gsGoalsAllowed .~ 4
& gYtd . gsGoalsAgainst .~ 5
& gYtd . gsWins .~ 6
& gYtd . gsLosses .~ 7
& gYtd . gsTies .~ 8
& gLifetime . gsGames .~ 9
& gLifetime . gsMinsPlayed .~ 10
& gLifetime . gsGoalsAllowed .~ 11
& gLifetime . gsGoalsAgainst .~ 12
& gLifetime . gsWins .~ 13
& gLifetime . gsLosses .~ 14
& gLifetime . gsTies .~ 15
2019-08-16 11:49:04 -04:00
db :: Database
db = newDatabase
& dbPlayers .~ [player]
& dbGoalies .~ [goalie]
2019-08-19 09:31:24 -04:00
& dbGames .~ 1
2019-08-16 11:49:04 -04:00
2019-08-10 10:01:36 -04:00
playerJSON :: ByteString
playerJSON = [r|
{ "number": 1
, "name": "Joe"
, "position": "centre"
, "ytd":
{ "goals": 2
, "assists": 3
, "penalty_mins": 4
}
, "lifetime":
{ "goals": 5
, "assists": 6
, "penalty_mins": 7
}
}|]
2019-08-11 10:24:39 -04:00
goalieJSON :: ByteString
goalieJSON = [r|
{ "number": 1
, "name": "Joe"
, "ytd":
{ "games": 2
, "mins_played": 3
, "goals_allowed": 4
, "goals_against": 5
, "wins": 6
, "losses": 7
, "ties": 8
}
, "lifetime":
{ "games": 9
, "mins_played": 10
, "goals_allowed": 11
, "goals_against": 12
, "wins": 13
, "losses": 14
, "ties": 15
}
}|]
2019-08-16 11:49:04 -04:00
dbJSON :: ByteString
dbJSON = [r|
{ "players":
[ |] <> playerJSON <> [r| ]
, "goalies":
[ |] <> goalieJSON <> [r| ]
2019-08-19 09:31:24 -04:00
, "games": 1
2019-08-16 11:49:04 -04:00
}|]