Skip to content

Commit ba09d14

Browse files
authored
Merge pull request #30 from haskell-servant/jsonEquality
Add jsonEquality to compare JSON APIs
2 parents ebe8ea6 + 0bdd1f2 commit ba09d14

File tree

4 files changed

+73
-0
lines changed

4 files changed

+73
-0
lines changed

servant-quickcheck/servant-quickcheck.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,7 @@ test-suite spec
8484
other-modules: Servant.QuickCheck.InternalSpec
8585
build-depends: base == 4.*
8686
, base-compat
87+
, aeson
8788
, servant-quickcheck
8889
, bytestring
8990
, hspec

servant-quickcheck/src/Servant/QuickCheck.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ module Servant.QuickCheck
4949
-- represents other means of checking equality
5050
-- *** Useful @ResponseEquality@s
5151
, bodyEquality
52+
, jsonEquality
5253
, allEquality
5354
-- ** Response equality type
5455
, ResponseEquality(..)

servant-quickcheck/src/Servant/QuickCheck/Internal/Equality.hs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,8 @@
11
module Servant.QuickCheck.Internal.Equality where
22

3+
import Data.Aeson (Value, decode, decodeStrict)
4+
import Data.ByteString (ByteString)
5+
import qualified Data.ByteString.Lazy as LB
36
import Data.Function (on)
47
import Network.HTTP.Client (Response, responseBody)
58
import Prelude.Compat
@@ -23,3 +26,25 @@ allEquality = ResponseEquality (==)
2326
-- /Since 0.0.0.0/
2427
bodyEquality :: Eq b => ResponseEquality b
2528
bodyEquality = ResponseEquality ((==) `on` responseBody)
29+
30+
jsonEquality :: (JsonEq b) => ResponseEquality b
31+
jsonEquality = ResponseEquality (jsonEq `on` responseBody)
32+
33+
class JsonEq a where
34+
decode' :: a -> Maybe Value
35+
jsonEq :: a -> a -> Bool
36+
jsonEq first second = compareDecodedResponses (decode' first) (decode' second)
37+
38+
instance JsonEq LB.ByteString where
39+
decode' = decode
40+
41+
instance JsonEq ByteString where
42+
decode' = decodeStrict
43+
44+
compareDecodedResponses :: Maybe Value -> Maybe Value -> Bool
45+
compareDecodedResponses resp1 resp2 =
46+
case resp1 of
47+
Nothing -> False -- if decoding fails we assume failure
48+
(Just r1) -> case resp2 of
49+
Nothing -> False -- another decode failure
50+
(Just r2) -> r1 == r2

servant-quickcheck/test/Servant/QuickCheck/InternalSpec.hs

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,34 @@ serversEqualSpec = describe "serversEqual" $ do
6969
show err `shouldContain` "Body: 2"
7070
show err `shouldContain` "Path: /failplz"
7171

72+
context "when JSON is equal but looks a bit different as a ByteString" $ do
73+
74+
it "sanity check: different whitespace same JSON objects bodyEquality fails" $ do
75+
FailedWith err <- withServantServer jsonApi jsonServer1 $ \burl1 ->
76+
withServantServer jsonApi jsonServer2 $ \burl2 -> do
77+
evalExample $ serversEqual jsonApi burl1 burl2 args bodyEquality
78+
show err `shouldContain` "Server equality failed"
79+
80+
it "jsonEquality considers equal JSON apis equal regardless of key ordering or whitespace" $ do
81+
withServantServerAndContext jsonApi ctx jsonServer1 $ \burl1 ->
82+
withServantServerAndContext jsonApi ctx jsonServer2 $ \burl2 ->
83+
serversEqual jsonApi burl1 burl2 args jsonEquality
84+
85+
it "sees when JSON apis are not equal because any value is different" $ do
86+
FailedWith err <- withServantServer jsonApi jsonServer2 $ \burl1 ->
87+
withServantServer jsonApi jsonServer3 $ \burl2 -> do
88+
evalExample $ serversEqual jsonApi burl1 burl2 args jsonEquality
89+
show err `shouldContain` "Server equality failed"
90+
show err `shouldContain` "Path: /jsonComparison"
91+
92+
it "sees when JSON apis are not equal due to different keys but same values" $ do
93+
FailedWith err <- withServantServer jsonApi jsonServer2 $ \burl1 ->
94+
withServantServer jsonApi jsonServer4 $ \burl2 -> do
95+
evalExample $ serversEqual jsonApi burl1 burl2 args jsonEquality
96+
show err `shouldContain` "Server equality failed"
97+
show err `shouldContain` "Path: /jsonComparison"
98+
99+
72100
serverSatisfiesSpec :: Spec
73101
serverSatisfiesSpec = describe "serverSatisfies" $ do
74102

@@ -262,6 +290,24 @@ octetAPI = Proxy
262290
serverOctetAPI :: IO (Server OctetAPI)
263291
serverOctetAPI = return $ return "blah"
264292

293+
type JsonApi = "jsonComparison" :> Get '[OctetStream] BS.ByteString
294+
295+
jsonApi :: Proxy JsonApi
296+
jsonApi = Proxy
297+
298+
jsonServer1 :: IO (Server JsonApi)
299+
jsonServer1 = return $ return "{ \"b\": [\"b\"], \"a\": 1 }" -- whitespace, ordering different
300+
301+
jsonServer2 :: IO (Server JsonApi)
302+
jsonServer2 = return $ return "{\"a\": 1,\"b\":[\"b\"]}"
303+
304+
jsonServer3 :: IO (Server JsonApi)
305+
jsonServer3 = return $ return "{\"a\": 2, \"b\": [\"b\"]}"
306+
307+
jsonServer4 :: IO (Server JsonApi)
308+
jsonServer4 = return $ return "{\"c\": 1, \"d\": [\"b\"]}"
309+
310+
265311
ctx :: Context '[BasicAuthCheck ()]
266312
ctx = BasicAuthCheck (const . return $ NoSuchUser) :. EmptyContext
267313
------------------------------------------------------------------------------

0 commit comments

Comments
 (0)