better JSON testing

This commit is contained in:
Jonathan Lamothe 2019-08-26 23:55:02 -04:00
parent c72ccf80bf
commit 954490fc6d
2 changed files with 92 additions and 103 deletions

View File

@ -26,7 +26,6 @@ dependencies:
- microlens-th >= 0.4.2.3 && < 0.5 - microlens-th >= 0.4.2.3 && < 0.5
- ncurses >= 0.2.16 && < 0.3 - ncurses >= 0.2.16 && < 0.3
- random >= 1.1 && < 1.2 - random >= 1.1 && < 1.2
- raw-strings-qq >= 1.1 && < 1.2
- transformers >= 0.5.6.2 && < 0.6 - transformers >= 0.5.6.2 && < 0.6
- bytestring - bytestring
- microlens - microlens
@ -56,3 +55,4 @@ tests:
dependencies: dependencies:
- mtlstats - mtlstats
- hspec >= 2.7.1 && < 2.8 - hspec >= 2.7.1 && < 2.8
- unordered-containers

View File

@ -19,15 +19,17 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-}
module TypesSpec (spec) where module TypesSpec (spec) where
import Data.Aeson (decode, encode) import Data.Aeson (FromJSON, ToJSON, decode, encode, toJSON)
import Data.Aeson.Types (Value (Object))
import Data.ByteString.Lazy (ByteString) import Data.ByteString.Lazy (ByteString)
import qualified Data.HashMap.Strict as HM
import Lens.Micro ((&), (^.), (.~), (?~)) import Lens.Micro ((&), (^.), (.~), (?~))
import Test.Hspec (Spec, context, describe, it, shouldBe) import Test.Hspec (Spec, context, describe, it, shouldBe)
import Text.RawString.QQ (r)
import Mtlstats.Types import Mtlstats.Types
import qualified Types.MenuSpec as Menu import qualified Types.MenuSpec as Menu
@ -35,9 +37,9 @@ import qualified Types.MenuSpec as Menu
spec :: Spec spec :: Spec
spec = describe "Mtlstats.Types" $ do spec = describe "Mtlstats.Types" $ do
playerSpec playerSpec
pPointsSpec
goalieSpec goalieSpec
databaseSpec databaseSpec
pPointsSpec
gameTypeLSpec gameTypeLSpec
otherTeamLSpec otherTeamLSpec
homeScoreLSpec homeScoreLSpec
@ -46,15 +48,13 @@ spec = describe "Mtlstats.Types" $ do
Menu.spec Menu.spec
playerSpec :: Spec playerSpec :: Spec
playerSpec = describe "Player" $ do playerSpec = describe "Player" $ jsonSpec player playerJSON
describe "decode" $ goalieSpec :: Spec
it "should decode" $ goalieSpec = describe "Goalie" $ jsonSpec goalie goalieJSON
decode playerJSON `shouldBe` Just player
describe "encode" $ databaseSpec :: Spec
it "should encode" $ databaseSpec = describe "Database" $ jsonSpec db dbJSON
decode (encode player) `shouldBe` Just player
pPointsSpec :: Spec pPointsSpec :: Spec
pPointsSpec = describe "pPoints" $ mapM_ pPointsSpec = describe "pPoints" $ mapM_
@ -74,28 +74,6 @@ pPointsSpec = describe "pPoints" $ mapM_
, ( 2, 3, 5 ) , ( 2, 3, 5 )
] ]
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
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
gameTypeLSpec :: Spec gameTypeLSpec :: Spec
gameTypeLSpec = describe "gameTypeL" $ do gameTypeLSpec = describe "gameTypeL" $ do
@ -233,31 +211,85 @@ teamScoreSpec = describe "teamScore" $ do
it "should return 2" $ it "should return 2" $
teamScore (s AwayGame) `shouldBe` Just 2 teamScore (s AwayGame) `shouldBe` Just 2
jsonSpec
:: (Eq a, Show a, FromJSON a, ToJSON a)
=> a
-> Value
-> Spec
jsonSpec x j = do
describe "decode" $
it "should decode" $
decode (encode j) `shouldBe` Just x
describe "toJSON" $
it "should encode" $
decode (encode $ toJSON x) `shouldBe` Just x
describe "toEncoding" $
it "should encode" $
decode (encode x) `shouldBe` Just x
player :: Player player :: Player
player = newPlayer 1 "Joe" "centre" player = newPlayer 1 "Joe" "centre"
& pYtd . psGoals .~ 2 & pYtd .~ playerStats 1
& pYtd . psAssists .~ 3 & pLifetime .~ playerStats 2
& pYtd . psPMin .~ 4
& pLifetime . psGoals .~ 5 playerJSON :: Value
& pLifetime . psAssists .~ 6 playerJSON = Object $ HM.fromList
& pLifetime . psPMin .~ 7 [ ( "number", toJSON (1 :: Int) )
, ( "name", toJSON ("Joe" :: String) )
, ( "position", toJSON ("centre" :: String) )
, ( "ytd", playerStatsJSON 1 )
, ( "lifetime", playerStatsJSON 2 )
]
playerStats :: Int -> PlayerStats
playerStats n = newPlayerStats
& psGoals .~ n
& psAssists .~ n + 1
& psPMin .~ n + 2
playerStatsJSON :: Int -> Value
playerStatsJSON n = Object $ HM.fromList
[ ( "goals", toJSON n )
, ( "assists", toJSON $ n + 1 )
, ( "penalty_mins", toJSON $ n + 2 )
]
goalie :: Goalie goalie :: Goalie
goalie = newGoalie 1 "Joe" goalie = newGoalie 1 "Joe"
& gYtd . gsGames .~ 2 & gYtd .~ goalieStats 1
& gYtd . gsMinsPlayed .~ 3 & gLifetime .~ goalieStats 2
& gYtd . gsGoalsAllowed .~ 4
& gYtd . gsGoalsAgainst .~ 5 goalieJSON :: Value
& gYtd . gsWins .~ 6 goalieJSON = Object $ HM.fromList
& gYtd . gsLosses .~ 7 [ ( "number", toJSON (1 :: Int) )
& gYtd . gsTies .~ 8 , ( "name", toJSON ("Joe" :: String ) )
& gLifetime . gsGames .~ 9 , ( "ytd", goalieStatsJSON 1 )
& gLifetime . gsMinsPlayed .~ 10 , ( "lifetime", goalieStatsJSON 2 )
& gLifetime . gsGoalsAllowed .~ 11 ]
& gLifetime . gsGoalsAgainst .~ 12
& gLifetime . gsWins .~ 13 goalieStats :: Int -> GoalieStats
& gLifetime . gsLosses .~ 14 goalieStats n = newGoalieStats
& gLifetime . gsTies .~ 15 & gsGames .~ n
& gsMinsPlayed .~ n + 1
& gsGoalsAllowed .~ n + 2
& gsGoalsAgainst .~ n + 3
& gsWins .~ n + 4
& gsLosses .~ n + 5
& gsTies .~ n + 6
goalieStatsJSON :: Int -> Value
goalieStatsJSON n = Object $ HM.fromList
[ ( "games", toJSON n )
, ( "mins_played", toJSON $ n + 1 )
, ( "goals_allowed", toJSON $ n + 2 )
, ( "goals_against", toJSON $ n + 3 )
, ( "wins", toJSON $ n + 4 )
, ( "losses", toJSON $ n + 5 )
, ( "ties", toJSON $ n + 6 )
]
db :: Database db :: Database
db = newDatabase db = newDatabase
@ -265,52 +297,9 @@ db = newDatabase
& dbGoalies .~ [goalie] & dbGoalies .~ [goalie]
& dbGames .~ 1 & dbGames .~ 1
playerJSON :: ByteString dbJSON :: Value
playerJSON = [r| dbJSON = Object $ HM.fromList
{ "number": 1 [ ( "players", toJSON [playerJSON] )
, "name": "Joe" , ( "goalies", toJSON [goalieJSON] )
, "position": "centre" , ( "games", toJSON (1 :: Int) )
, "ytd": ]
{ "goals": 2
, "assists": 3
, "penalty_mins": 4
}
, "lifetime":
{ "goals": 5
, "assists": 6
, "penalty_mins": 7
}
}|]
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
}
}|]
dbJSON :: ByteString
dbJSON = [r|
{ "players":
[ |] <> playerJSON <> [r| ]
, "goalies":
[ |] <> goalieJSON <> [r| ]
, "games": 1
}|]