Skip to content

Commit 08fcbcd

Browse files
authored
Merge pull request #569 from phadej/issue-568
Fix #568: object is unordered
2 parents de79f6b + 059e2ff commit 08fcbcd

File tree

1 file changed

+141
-115
lines changed

1 file changed

+141
-115
lines changed

Diff for: tests/SerializationFormatSpec.hs

+141-115
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import Control.Applicative (Const(..))
2222
import Data.Aeson (FromJSON(..), decode, encode, genericParseJSON, genericToEncoding, genericToJSON)
2323
import Data.Aeson.Types (Options(..), SumEncoding(..), ToJSON(..), defaultOptions)
2424
import Data.Fixed (Pico)
25+
import Data.Foldable (for_, toList)
2526
import Data.Functor.Compose (Compose(..))
2627
import Data.Functor.Identity (Identity(..))
2728
import Data.Functor.Product (Product(..))
@@ -65,132 +66,144 @@ tests =
6566
jsonExamples :: [Example]
6667
jsonExamples =
6768
[
68-
Example "Either Left" "{\"Left\":1}" (Left 1 :: Either Int Int)
69-
, Example "Either Right" "{\"Right\":1}" (Right 1 :: Either Int Int)
70-
, Example "Nothing" "null" (Nothing :: Maybe Int)
71-
, Example "Just" "1" (Just 1 :: Maybe Int)
72-
, Example "Proxy Int" "null" (Proxy :: Proxy Int)
73-
, Example "Tagged Char Int" "1" (Tagged 1 :: Tagged Char Int)
69+
example "Either Left" "{\"Left\":1}" (Left 1 :: Either Int Int)
70+
, example "Either Right" "{\"Right\":1}" (Right 1 :: Either Int Int)
71+
, example "Nothing" "null" (Nothing :: Maybe Int)
72+
, example "Just" "1" (Just 1 :: Maybe Int)
73+
, example "Proxy Int" "null" (Proxy :: Proxy Int)
74+
, example "Tagged Char Int" "1" (Tagged 1 :: Tagged Char Int)
7475
#if __GLASGOW_HASKELL__ >= 708
7576
-- Test Tagged instance is polykinded
76-
, Example "Tagged 123 Int" "1" (Tagged 1 :: Tagged 123 Int)
77+
, example "Tagged 123 Int" "1" (Tagged 1 :: Tagged 123 Int)
7778
#endif
78-
, Example "Const Char Int" "\"c\"" (Const 'c' :: Const Char Int)
79-
, Example "Tuple" "[1,2]" ((1, 2) :: (Int, Int))
80-
, Example "NonEmpty" "[1,2,3]" (1 :| [2, 3] :: NonEmpty Int)
81-
, Example "Seq" "[1,2,3]" (Seq.fromList [1, 2, 3] :: Seq.Seq Int)
82-
, Example "DList" "[1,2,3]" (DList.fromList [1, 2, 3] :: DList.DList Int)
83-
, Example "()" "[]" ()
84-
85-
, Example "HashMap Int Int" "{\"0\":1,\"2\":3}" (HM.fromList [(0,1),(2,3)] :: HM.HashMap Int Int)
86-
, Example "Map Int Int" "{\"0\":1,\"2\":3}" (M.fromList [(0,1),(2,3)] :: M.Map Int Int)
87-
, Example "Map (Tagged Int Int) Int" "{\"0\":1,\"2\":3}" (M.fromList [(Tagged 0,1),(Tagged 2,3)] :: M.Map (Tagged Int Int) Int)
88-
, Example "Map [Int] Int" "[[[0],1],[[2],3]]" (M.fromList [([0],1),([2],3)] :: M.Map [Int] Int)
89-
, Example "Map [Char] Int" "{\"ab\":1,\"cd\":3}" (M.fromList [("ab",1),("cd",3)] :: M.Map String Int)
90-
, Example "Map [I Char] Int" "{\"ab\":1,\"cd\":3}" (M.fromList [(map pure "ab",1),(map pure "cd",3)] :: M.Map [I Char] Int)
91-
92-
, Example "nan :: Double" "null" (Approx $ 0/0 :: Approx Double)
93-
94-
, Example "Ordering LT" "\"LT\"" LT
95-
, Example "Ordering EQ" "\"EQ\"" EQ
96-
, Example "Ordering GT" "\"GT\"" GT
97-
98-
, Example "Float" "3.14" (3.14 :: Float)
99-
, Example "Pico" "3.14" (3.14 :: Pico)
100-
, Example "Scientific" "3.14" (3.14 :: Scientific)
101-
102-
, Example "UUID" "\"c2cc10e1-57d6-4b6f-9899-38d972112d8c\"" $ UUID.fromWords
79+
, example "Const Char Int" "\"c\"" (Const 'c' :: Const Char Int)
80+
, example "Tuple" "[1,2]" ((1, 2) :: (Int, Int))
81+
, example "NonEmpty" "[1,2,3]" (1 :| [2, 3] :: NonEmpty Int)
82+
, example "Seq" "[1,2,3]" (Seq.fromList [1, 2, 3] :: Seq.Seq Int)
83+
, example "DList" "[1,2,3]" (DList.fromList [1, 2, 3] :: DList.DList Int)
84+
, example "()" "[]" ()
85+
86+
, Example "HashMap Int Int"
87+
[ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
88+
(HM.fromList [(0,1),(2,3)] :: HM.HashMap Int Int)
89+
, Example "Map Int Int"
90+
[ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
91+
(M.fromList [(0,1),(2,3)] :: M.Map Int Int)
92+
, Example "Map (Tagged Int Int) Int"
93+
[ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
94+
(M.fromList [(Tagged 0,1),(Tagged 2,3)] :: M.Map (Tagged Int Int) Int)
95+
, example "Map [Int] Int"
96+
"[[[0],1],[[2],3]]"
97+
(M.fromList [([0],1),([2],3)] :: M.Map [Int] Int)
98+
, Example "Map [Char] Int"
99+
[ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ]
100+
(M.fromList [("ab",1),("cd",3)] :: M.Map String Int)
101+
, Example "Map [I Char] Int"
102+
[ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ]
103+
(M.fromList [(map pure "ab",1),(map pure "cd",3)] :: M.Map [I Char] Int)
104+
105+
, example "nan :: Double" "null" (Approx $ 0/0 :: Approx Double)
106+
107+
, example "Ordering LT" "\"LT\"" LT
108+
, example "Ordering EQ" "\"EQ\"" EQ
109+
, example "Ordering GT" "\"GT\"" GT
110+
111+
, example "Float" "3.14" (3.14 :: Float)
112+
, example "Pico" "3.14" (3.14 :: Pico)
113+
, example "Scientific" "3.14" (3.14 :: Scientific)
114+
115+
, example "UUID" "\"c2cc10e1-57d6-4b6f-9899-38d972112d8c\"" $ UUID.fromWords
103116
0xc2cc10e1 0x57d64b6f 0x989938d9 0x72112d8c
104117

105-
, Example "Set Int" "[1,2,3]" (Set.fromList [3, 2, 1] :: Set.Set Int)
106-
, Example "IntSet" "[1,2,3]" (IntSet.fromList [3, 2, 1])
107-
, Example "IntMap" "[[1,2],[3,4]]" (IntMap.fromList [(3,4), (1,2)] :: IntMap.IntMap Int)
108-
, Example "Vector" "[1,2,3]" (Vector.fromList [1, 2, 3] :: Vector.Vector Int)
109-
, Example "HashSet Int" "[1,2,3]" (HashSet.fromList [3, 2, 1] :: HashSet.HashSet Int)
110-
, Example "Tree Int" "[1,[[2,[[3,[]],[4,[]]]],[5,[]]]]" (let n = Tree.Node in n 1 [n 2 [n 3 [], n 4 []], n 5 []] :: Tree.Tree Int)
118+
, example "Set Int" "[1,2,3]" (Set.fromList [3, 2, 1] :: Set.Set Int)
119+
, example "IntSet" "[1,2,3]" (IntSet.fromList [3, 2, 1])
120+
, example "IntMap" "[[1,2],[3,4]]" (IntMap.fromList [(3,4), (1,2)] :: IntMap.IntMap Int)
121+
, example "Vector" "[1,2,3]" (Vector.fromList [1, 2, 3] :: Vector.Vector Int)
122+
, example "HashSet Int" "[1,2,3]" (HashSet.fromList [3, 2, 1] :: HashSet.HashSet Int)
123+
, example "Tree Int" "[1,[[2,[[3,[]],[4,[]]]],[5,[]]]]" (let n = Tree.Node in n 1 [n 2 [n 3 [], n 4 []], n 5 []] :: Tree.Tree Int)
111124

112125
-- Three separate cases, as ordering in HashMap is not defined
113-
, Example "HashMap Float Int, NaN" "{\"NaN\":1}" (Approx $ HM.singleton (0/0) 1 :: Approx (HM.HashMap Float Int))
114-
, Example "HashMap Float Int, Infinity" "{\"Infinity\":1}" (HM.singleton (1/0) 1 :: HM.HashMap Float Int)
115-
, Example "HashMap Float Int, +Infinity" "{\"-Infinity\":1}" (HM.singleton (negate 1/0) 1 :: HM.HashMap Float Int)
126+
, example "HashMap Float Int, NaN" "{\"NaN\":1}" (Approx $ HM.singleton (0/0) 1 :: Approx (HM.HashMap Float Int))
127+
, example "HashMap Float Int, Infinity" "{\"Infinity\":1}" (HM.singleton (1/0) 1 :: HM.HashMap Float Int)
128+
, example "HashMap Float Int, +Infinity" "{\"-Infinity\":1}" (HM.singleton (negate 1/0) 1 :: HM.HashMap Float Int)
116129

117130
-- Functors
118-
, Example "Identity Int" "1" (pure 1 :: Identity Int)
119-
120-
, Example "Identity Char" "\"x\"" (pure 'x' :: Identity Char)
121-
, Example "Identity String" "\"foo\"" (pure "foo" :: Identity String)
122-
, Example "[Identity Char]" "\"xy\"" ([pure 'x', pure 'y'] :: [Identity Char])
123-
124-
, Example "Maybe Char" "\"x\"" (pure 'x' :: Maybe Char)
125-
, Example "Maybe String" "\"foo\"" (pure "foo" :: Maybe String)
126-
, Example "Maybe [Identity Char]" "\"xy\"" (pure [pure 'x', pure 'y'] :: Maybe [Identity Char])
127-
128-
, Example "Day; year >= 1000" "\"1999-10-12\"" (fromGregorian 1999 10 12)
129-
, Example "Day; year > 0 && < 1000" "\"0500-03-04\"" (fromGregorian 500 3 4)
130-
, Example "Day; year == 0" "\"0000-02-20\"" (fromGregorian 0 2 20)
131-
, Example "Day; year < 0" "\"-0234-01-01\"" (fromGregorian (-234) 1 1)
132-
, Example "Day; year < -1000" "\"-1234-01-01\"" (fromGregorian (-1234) 1 1)
133-
134-
, Example "Product I Maybe Int" "[1,2]" (Pair (pure 1) (pure 2) :: Product I Maybe Int)
135-
, Example "Product I Maybe Int" "[1,null]" (Pair (pure 1) Nothing :: Product I Maybe Int)
136-
, Example "Product I [] Char" "[\"a\",\"foo\"]" (Pair (pure 'a') "foo" :: Product I [] Char)
137-
138-
, Example "Sum I [] Int: InL" "{\"InL\":1}" (InL (pure 1) :: Sum I [] Int)
139-
, Example "Sum I [] Int: InR" "{\"InR\":[1,2]}" (InR [1, 2] :: Sum I [] Int)
140-
, Example "Sum I [] Char: InR" "{\"InR\":\"foo\"}" (InR "foo" :: Sum I [] Char)
141-
142-
, Example "Compose I I Int" "1" (pure 1 :: Compose I I Int)
143-
, Example "Compose I [] Int" "[1]" (pure 1 :: Compose I [] Int)
144-
, Example "Compose [] I Int" "[1]" (pure 1 :: Compose [] I Int)
145-
, Example "Compose [] [] Int" "[[1]]" (pure 1 :: Compose [] [] Int)
146-
147-
, Example "Compose I I Char" "\"x\"" (pure 'x' :: Compose I I Char)
148-
, Example "Compose I [] Char" "\"x\"" (pure 'x' :: Compose I [] Char)
149-
, Example "Compose [] I Char" "\"x\"" (pure 'x' :: Compose [] I Char)
150-
, Example "Compose [] [] Char" "[\"x\"]" (pure 'x' :: Compose [] [] Char)
151-
152-
, Example "Compose3 I I I Char" "\"x\"" (pure 'x' :: Compose3 I I I Char)
153-
, Example "Compose3 I I [] Char" "\"x\"" (pure 'x' :: Compose3 I I [] Char)
154-
, Example "Compose3 I [] I Char" "\"x\"" (pure 'x' :: Compose3 I [] I Char)
155-
, Example "Compose3 I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3 I [] [] Char)
156-
, Example "Compose3 [] I I Char" "\"x\"" (pure 'x' :: Compose3 [] I I Char)
157-
, Example "Compose3 [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3 [] I [] Char)
158-
, Example "Compose3 [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3 [] [] I Char)
159-
, Example "Compose3 [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3 [] [] [] Char)
160-
161-
, Example "Compose3' I I I Char" "\"x\"" (pure 'x' :: Compose3' I I I Char)
162-
, Example "Compose3' I I [] Char" "\"x\"" (pure 'x' :: Compose3' I I [] Char)
163-
, Example "Compose3' I [] I Char" "\"x\"" (pure 'x' :: Compose3' I [] I Char)
164-
, Example "Compose3' I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3' I [] [] Char)
165-
, Example "Compose3' [] I I Char" "\"x\"" (pure 'x' :: Compose3' [] I I Char)
166-
, Example "Compose3' [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3' [] I [] Char)
167-
, Example "Compose3' [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3' [] [] I Char)
168-
, Example "Compose3' [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3' [] [] [] Char)
169-
170-
, Example "MyEither Int String: Left" "42" (MyLeft 42 :: MyEither Int String)
171-
, Example "MyEither Int String: Right" "\"foo\"" (MyRight "foo" :: MyEither Int String)
131+
, example "Identity Int" "1" (pure 1 :: Identity Int)
132+
133+
, example "Identity Char" "\"x\"" (pure 'x' :: Identity Char)
134+
, example "Identity String" "\"foo\"" (pure "foo" :: Identity String)
135+
, example "[Identity Char]" "\"xy\"" ([pure 'x', pure 'y'] :: [Identity Char])
136+
137+
, example "Maybe Char" "\"x\"" (pure 'x' :: Maybe Char)
138+
, example "Maybe String" "\"foo\"" (pure "foo" :: Maybe String)
139+
, example "Maybe [Identity Char]" "\"xy\"" (pure [pure 'x', pure 'y'] :: Maybe [Identity Char])
140+
141+
, example "Day; year >= 1000" "\"1999-10-12\"" (fromGregorian 1999 10 12)
142+
, example "Day; year > 0 && < 1000" "\"0500-03-04\"" (fromGregorian 500 3 4)
143+
, example "Day; year == 0" "\"0000-02-20\"" (fromGregorian 0 2 20)
144+
, example "Day; year < 0" "\"-0234-01-01\"" (fromGregorian (-234) 1 1)
145+
, example "Day; year < -1000" "\"-1234-01-01\"" (fromGregorian (-1234) 1 1)
146+
147+
, example "Product I Maybe Int" "[1,2]" (Pair (pure 1) (pure 2) :: Product I Maybe Int)
148+
, example "Product I Maybe Int" "[1,null]" (Pair (pure 1) Nothing :: Product I Maybe Int)
149+
, example "Product I [] Char" "[\"a\",\"foo\"]" (Pair (pure 'a') "foo" :: Product I [] Char)
150+
151+
, example "Sum I [] Int: InL" "{\"InL\":1}" (InL (pure 1) :: Sum I [] Int)
152+
, example "Sum I [] Int: InR" "{\"InR\":[1,2]}" (InR [1, 2] :: Sum I [] Int)
153+
, example "Sum I [] Char: InR" "{\"InR\":\"foo\"}" (InR "foo" :: Sum I [] Char)
154+
155+
, example "Compose I I Int" "1" (pure 1 :: Compose I I Int)
156+
, example "Compose I [] Int" "[1]" (pure 1 :: Compose I [] Int)
157+
, example "Compose [] I Int" "[1]" (pure 1 :: Compose [] I Int)
158+
, example "Compose [] [] Int" "[[1]]" (pure 1 :: Compose [] [] Int)
159+
160+
, example "Compose I I Char" "\"x\"" (pure 'x' :: Compose I I Char)
161+
, example "Compose I [] Char" "\"x\"" (pure 'x' :: Compose I [] Char)
162+
, example "Compose [] I Char" "\"x\"" (pure 'x' :: Compose [] I Char)
163+
, example "Compose [] [] Char" "[\"x\"]" (pure 'x' :: Compose [] [] Char)
164+
165+
, example "Compose3 I I I Char" "\"x\"" (pure 'x' :: Compose3 I I I Char)
166+
, example "Compose3 I I [] Char" "\"x\"" (pure 'x' :: Compose3 I I [] Char)
167+
, example "Compose3 I [] I Char" "\"x\"" (pure 'x' :: Compose3 I [] I Char)
168+
, example "Compose3 I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3 I [] [] Char)
169+
, example "Compose3 [] I I Char" "\"x\"" (pure 'x' :: Compose3 [] I I Char)
170+
, example "Compose3 [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3 [] I [] Char)
171+
, example "Compose3 [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3 [] [] I Char)
172+
, example "Compose3 [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3 [] [] [] Char)
173+
174+
, example "Compose3' I I I Char" "\"x\"" (pure 'x' :: Compose3' I I I Char)
175+
, example "Compose3' I I [] Char" "\"x\"" (pure 'x' :: Compose3' I I [] Char)
176+
, example "Compose3' I [] I Char" "\"x\"" (pure 'x' :: Compose3' I [] I Char)
177+
, example "Compose3' I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3' I [] [] Char)
178+
, example "Compose3' [] I I Char" "\"x\"" (pure 'x' :: Compose3' [] I I Char)
179+
, example "Compose3' [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3' [] I [] Char)
180+
, example "Compose3' [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3' [] [] I Char)
181+
, example "Compose3' [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3' [] [] [] Char)
182+
183+
, example "MyEither Int String: Left" "42" (MyLeft 42 :: MyEither Int String)
184+
, example "MyEither Int String: Right" "\"foo\"" (MyRight "foo" :: MyEither Int String)
172185

173186
-- newtypes from Monoid/Semigroup
174-
, Example "Monoid.Dual Int" "2" (pure 2 :: Monoid.Dual Int)
175-
, Example "Monoid.First Int" "2" (pure 2 :: Monoid.First Int)
176-
, Example "Monoid.Last Int" "2" (pure 2 :: Monoid.Last Int)
177-
, Example "Semigroup.Min Int" "2" (pure 2 :: Semigroup.Min Int)
178-
, Example "Semigroup.Max Int" "2" (pure 2 :: Semigroup.Max Int)
179-
, Example "Semigroup.First Int" "2" (pure 2 :: Semigroup.First Int)
180-
, Example "Semigroup.Last Int" "2" (pure 2 :: Semigroup.Last Int)
181-
, Example "Semigroup.WrappedMonoid Int" "2" (Semigroup.WrapMonoid 2 :: Semigroup.WrappedMonoid Int)
182-
, Example "Semigroup.Option Just" "2" (pure 2 :: Semigroup.Option Int)
183-
, Example "Semigroup.Option Nothing" "null" (Semigroup.Option (Nothing :: Maybe Bool))
187+
, example "Monoid.Dual Int" "2" (pure 2 :: Monoid.Dual Int)
188+
, example "Monoid.First Int" "2" (pure 2 :: Monoid.First Int)
189+
, example "Monoid.Last Int" "2" (pure 2 :: Monoid.Last Int)
190+
, example "Semigroup.Min Int" "2" (pure 2 :: Semigroup.Min Int)
191+
, example "Semigroup.Max Int" "2" (pure 2 :: Semigroup.Max Int)
192+
, example "Semigroup.First Int" "2" (pure 2 :: Semigroup.First Int)
193+
, example "Semigroup.Last Int" "2" (pure 2 :: Semigroup.Last Int)
194+
, example "Semigroup.WrappedMonoid Int" "2" (Semigroup.WrapMonoid 2 :: Semigroup.WrappedMonoid Int)
195+
, example "Semigroup.Option Just" "2" (pure 2 :: Semigroup.Option Int)
196+
, example "Semigroup.Option Nothing" "null" (Semigroup.Option (Nothing :: Maybe Bool))
184197
]
185198

186199
jsonEncodingExamples :: [Example]
187200
jsonEncodingExamples =
188201
[
189202
-- Maybe serialising is lossy
190203
-- https://github.com/bos/aeson/issues/376
191-
Example "Just Nothing" "null" (Just Nothing :: Maybe (Maybe Int))
204+
example "Just Nothing" "null" (Just Nothing :: Maybe (Maybe Int))
192205
-- infinities cannot be recovered, null is decoded as NaN
193-
, Example "inf :: Double" "null" (Approx $ 1/0 :: Approx Double)
206+
, example "inf :: Double" "null" (Approx $ 1/0 :: Approx Double)
194207
]
195208

196209
jsonDecodingExamples :: [Example]
@@ -214,11 +227,15 @@ jsonDecodingExamples = [
214227
data Example where
215228
Example
216229
:: (Eq a, Show a, ToJSON a, FromJSON a)
217-
=> String -> L.ByteString -> a -> Example
230+
=> String -> [L.ByteString] -> a -> Example -- empty bytestring will fail, any p [] == False
218231
MaybeExample
219232
:: (Eq a, Show a, FromJSON a)
220233
=> String -> L.ByteString -> Maybe a -> Example
221234

235+
example :: (Eq a, Show a, ToJSON a, FromJSON a)
236+
=> String -> L.ByteString -> a -> Example
237+
example n bs x = Example n [bs] x
238+
222239
data MyEither a b = MyLeft a | MyRight b
223240
deriving (Generic, Show, Eq)
224241

@@ -230,16 +247,25 @@ instance (FromJSON a, FromJSON b) => FromJSON (MyEither a b) where
230247
parseJSON = genericParseJSON defaultOptions { sumEncoding = UntaggedValue }
231248

232249
assertJsonExample :: Example -> Test
233-
assertJsonExample (Example name bs val) = testCase name $ do
234-
assertEqual "encode" bs (encode val)
235-
assertEqual "encode/via value" bs (encode $ toJSON val)
236-
assertEqual "decode" (Just val) (decode bs)
250+
assertJsonExample (Example name bss val) = testCase name $ do
251+
assertSomeEqual "encode" bss (encode val)
252+
assertSomeEqual "encode/via value" bss (encode $ toJSON val)
253+
for_ bss $ \bs ->
254+
assertEqual "decode" (Just val) (decode bs)
237255
assertJsonExample (MaybeExample name bs mval) = testCase name $
238256
assertEqual "decode" mval (decode bs)
239257

240258
assertJsonEncodingExample :: Example -> Test
241-
assertJsonEncodingExample (Example name bs val) = testCase name $ do
242-
assertEqual "encode" bs (encode val)
243-
assertEqual "encode/via value" bs (encode $ toJSON val)
259+
assertJsonEncodingExample (Example name bss val) = testCase name $ do
260+
assertSomeEqual "encode" bss (encode val)
261+
assertSomeEqual "encode/via value" bss (encode $ toJSON val)
244262
assertJsonEncodingExample (MaybeExample name _ _) = testCase name $
245263
assertFailure "cannot encode MaybeExample"
264+
265+
assertSomeEqual :: (Eq a, Show a, Foldable f) => String -> f a -> a -> IO ()
266+
assertSomeEqual preface expected actual
267+
| actual `elem` expected = return ()
268+
| otherwise = assertFailure $ preface
269+
++ ": expecting one of " ++ show (toList expected)
270+
++ ", got " ++ show actual
271+

0 commit comments

Comments
 (0)