Skip to content

Commit 7bc9972

Browse files
committed
Improve test output by using QC's (===) instead of (==)
1 parent 1a3cd85 commit 7bc9972

File tree

1 file changed

+54
-55
lines changed

1 file changed

+54
-55
lines changed

tests/Properties/HashMapLazy.hs

Lines changed: 54 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -56,10 +56,10 @@ instance (Eq k, Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v)
5656
------------------------------------------------------------------------
5757
-- ** Instances
5858

59-
pEq :: [(Key, Int)] -> [(Key, Int)] -> Bool
59+
pEq :: [(Key, Int)] -> [(Key, Int)] -> Property
6060
pEq xs = (M.fromList xs ==) `eq` (HM.fromList xs ==)
6161

62-
pNeq :: [(Key, Int)] -> [(Key, Int)] -> Bool
62+
pNeq :: [(Key, Int)] -> [(Key, Int)] -> Property
6363
pNeq xs = (M.fromList xs /=) `eq` (HM.fromList xs /=)
6464

6565
-- We cannot compare to `Data.Map` as ordering is different.
@@ -104,10 +104,10 @@ pOrdEq xs ys = case (compare x y, x == y) of
104104
pReadShow :: [(Key, Int)] -> Bool
105105
pReadShow xs = M.fromList xs == read (show (M.fromList xs))
106106

107-
pFunctor :: [(Key, Int)] -> Bool
107+
pFunctor :: [(Key, Int)] -> Property
108108
pFunctor = fmap (+ 1) `eq_` fmap (+ 1)
109109

110-
pFoldable :: [(Int, Int)] -> Bool
110+
pFoldable :: [(Int, Int)] -> Property
111111
pFoldable = (List.sort . Foldable.foldr (:) []) `eq`
112112
(List.sort . Foldable.foldr (:) [])
113113

@@ -128,22 +128,22 @@ pHashable xs is salt =
128128
------------------------------------------------------------------------
129129
-- ** Basic interface
130130

131-
pSize :: [(Key, Int)] -> Bool
131+
pSize :: [(Key, Int)] -> Property
132132
pSize = M.size `eq` HM.size
133133

134-
pMember :: Key -> [(Key, Int)] -> Bool
134+
pMember :: Key -> [(Key, Int)] -> Property
135135
pMember k = M.member k `eq` HM.member k
136136

137-
pLookup :: Key -> [(Key, Int)] -> Bool
137+
pLookup :: Key -> [(Key, Int)] -> Property
138138
pLookup k = M.lookup k `eq` HM.lookup k
139139

140-
pLookupOperator :: Key -> [(Key, Int)] -> Bool
140+
pLookupOperator :: Key -> [(Key, Int)] -> Property
141141
pLookupOperator k = M.lookup k `eq` (HM.!? k)
142142

143-
pInsert :: Key -> Int -> [(Key, Int)] -> Bool
143+
pInsert :: Key -> Int -> [(Key, Int)] -> Property
144144
pInsert k v = M.insert k v `eq_` HM.insert k v
145145

146-
pDelete :: Key -> [(Key, Int)] -> Bool
146+
pDelete :: Key -> [(Key, Int)] -> Property
147147
pDelete k = M.delete k `eq_` HM.delete k
148148

149149
newtype AlwaysCollide = AC Int
@@ -172,25 +172,25 @@ pDeleteCollision k1 k2 k3 idx = (k1 /= k2) && (k2 /= k3) && (k1 /= k3) ==>
172172
| which == 2 = k1
173173
| otherwise = error "Impossible"
174174

175-
pInsertWith :: Key -> [(Key, Int)] -> Bool
175+
pInsertWith :: Key -> [(Key, Int)] -> Property
176176
pInsertWith k = M.insertWith (+) k 1 `eq_` HM.insertWith (+) k 1
177177

178-
pAdjust :: Key -> [(Key, Int)] -> Bool
178+
pAdjust :: Key -> [(Key, Int)] -> Property
179179
pAdjust k = M.adjust succ k `eq_` HM.adjust succ k
180180

181-
pUpdateAdjust :: Key -> [(Key, Int)] -> Bool
181+
pUpdateAdjust :: Key -> [(Key, Int)] -> Property
182182
pUpdateAdjust k = M.update (Just . succ) k `eq_` HM.update (Just . succ) k
183183

184-
pUpdateDelete :: Key -> [(Key, Int)] -> Bool
184+
pUpdateDelete :: Key -> [(Key, Int)] -> Property
185185
pUpdateDelete k = M.update (const Nothing) k `eq_` HM.update (const Nothing) k
186186

187-
pAlterAdjust :: Key -> [(Key, Int)] -> Bool
187+
pAlterAdjust :: Key -> [(Key, Int)] -> Property
188188
pAlterAdjust k = M.alter (fmap succ) k `eq_` HM.alter (fmap succ) k
189189

190-
pAlterInsert :: Key -> [(Key, Int)] -> Bool
190+
pAlterInsert :: Key -> [(Key, Int)] -> Property
191191
pAlterInsert k = M.alter (const $ Just 3) k `eq_` HM.alter (const $ Just 3) k
192192

193-
pAlterDelete :: Key -> [(Key, Int)] -> Bool
193+
pAlterDelete :: Key -> [(Key, Int)] -> Property
194194
pAlterDelete k = M.alter (const Nothing) k `eq_` HM.alter (const Nothing) k
195195

196196

@@ -203,29 +203,29 @@ pAlterF k f xs =
203203
===
204204
fmap toAscList (HM.alterF (apply f) k (HM.fromList xs))
205205

206-
pAlterFAdjust :: Key -> [(Key, Int)] -> Bool
206+
pAlterFAdjust :: Key -> [(Key, Int)] -> Property
207207
pAlterFAdjust k =
208208
runIdentity . M.alterF (Identity . fmap succ) k `eq_`
209209
runIdentity . HM.alterF (Identity . fmap succ) k
210210

211-
pAlterFInsert :: Key -> [(Key, Int)] -> Bool
211+
pAlterFInsert :: Key -> [(Key, Int)] -> Property
212212
pAlterFInsert k =
213213
runIdentity . M.alterF (const . Identity . Just $ 3) k `eq_`
214214
runIdentity . HM.alterF (const . Identity . Just $ 3) k
215215

216-
pAlterFInsertWith :: Key -> Fun Int Int -> [(Key, Int)] -> Bool
216+
pAlterFInsertWith :: Key -> Fun Int Int -> [(Key, Int)] -> Property
217217
pAlterFInsertWith k f =
218218
runIdentity . M.alterF (Identity . Just . maybe 3 (apply f)) k `eq_`
219219
runIdentity . HM.alterF (Identity . Just . maybe 3 (apply f)) k
220220

221-
pAlterFDelete :: Key -> [(Key, Int)] -> Bool
221+
pAlterFDelete :: Key -> [(Key, Int)] -> Property
222222
pAlterFDelete k =
223223
runIdentity . M.alterF (const (Identity Nothing)) k `eq_`
224224
runIdentity . HM.alterF (const (Identity Nothing)) k
225225

226226
pAlterFLookup :: Key
227227
-> Fun (Maybe A) B
228-
-> [(Key, A)] -> Bool
228+
-> [(Key, A)] -> Property
229229
pAlterFLookup k f =
230230
getConst . M.alterF (Const . apply f :: Maybe A -> Const B (Maybe A)) k
231231
`eq`
@@ -272,14 +272,14 @@ pNotSubmapInsert k v m = not (HM.member k m) ==> not (HM.isSubmapOf (HM.insert k
272272
------------------------------------------------------------------------
273273
-- ** Combine
274274

275-
pUnion :: [(Key, Int)] -> [(Key, Int)] -> Bool
275+
pUnion :: [(Key, Int)] -> [(Key, Int)] -> Property
276276
pUnion xs ys = M.union (M.fromList xs) `eq_` HM.union (HM.fromList xs) $ ys
277277

278-
pUnionWith :: [(Key, Int)] -> [(Key, Int)] -> Bool
278+
pUnionWith :: [(Key, Int)] -> [(Key, Int)] -> Property
279279
pUnionWith xs ys = M.unionWith (-) (M.fromList xs) `eq_`
280280
HM.unionWith (-) (HM.fromList xs) $ ys
281281

282-
pUnionWithKey :: [(Key, Int)] -> [(Key, Int)] -> Bool
282+
pUnionWithKey :: [(Key, Int)] -> [(Key, Int)] -> Property
283283
pUnionWithKey xs ys = M.unionWithKey go (M.fromList xs) `eq_`
284284
HM.unionWithKey go (HM.fromList xs) $ ys
285285
where
@@ -293,41 +293,41 @@ pUnions xss = M.toAscList (M.unions (map M.fromList xss)) ==
293293
------------------------------------------------------------------------
294294
-- ** Transformations
295295

296-
pMap :: [(Key, Int)] -> Bool
296+
pMap :: [(Key, Int)] -> Property
297297
pMap = M.map (+ 1) `eq_` HM.map (+ 1)
298298

299299
pTraverse :: [(Key, Int)] -> Bool
300300
pTraverse xs =
301301
List.sort (fmap (List.sort . M.toList) (M.traverseWithKey (\_ v -> [v + 1, v + 2]) (M.fromList (take 10 xs))))
302302
== List.sort (fmap (List.sort . HM.toList) (HM.traverseWithKey (\_ v -> [v + 1, v + 2]) (HM.fromList (take 10 xs))))
303303

304-
pMapKeys :: [(Int, Int)] -> Bool
304+
pMapKeys :: [(Int, Int)] -> Property
305305
pMapKeys = M.mapKeys (+1) `eq_` HM.mapKeys (+1)
306306

307307
------------------------------------------------------------------------
308308
-- ** Difference and intersection
309309

310-
pDifference :: [(Key, Int)] -> [(Key, Int)] -> Bool
310+
pDifference :: [(Key, Int)] -> [(Key, Int)] -> Property
311311
pDifference xs ys = M.difference (M.fromList xs) `eq_`
312312
HM.difference (HM.fromList xs) $ ys
313313

314-
pDifferenceWith :: [(Key, Int)] -> [(Key, Int)] -> Bool
314+
pDifferenceWith :: [(Key, Int)] -> [(Key, Int)] -> Property
315315
pDifferenceWith xs ys = M.differenceWith f (M.fromList xs) `eq_`
316316
HM.differenceWith f (HM.fromList xs) $ ys
317317
where
318318
f x y = if x == 0 then Nothing else Just (x - y)
319319

320-
pIntersection :: [(Key, Int)] -> [(Key, Int)] -> Bool
320+
pIntersection :: [(Key, Int)] -> [(Key, Int)] -> Property
321321
pIntersection xs ys =
322322
M.intersection (M.fromList xs)
323323
`eq_` HM.intersection (HM.fromList xs)
324324
$ ys
325325

326-
pIntersectionWith :: [(Key, Int)] -> [(Key, Int)] -> Bool
326+
pIntersectionWith :: [(Key, Int)] -> [(Key, Int)] -> Property
327327
pIntersectionWith xs ys = M.intersectionWith (-) (M.fromList xs) `eq_`
328328
HM.intersectionWith (-) (HM.fromList xs) $ ys
329329

330-
pIntersectionWithKey :: [(Key, Int)] -> [(Key, Int)] -> Bool
330+
pIntersectionWithKey :: [(Key, Int)] -> [(Key, Int)] -> Property
331331
pIntersectionWithKey xs ys = M.intersectionWithKey go (M.fromList xs) `eq_`
332332
HM.intersectionWithKey go (HM.fromList xs) $ ys
333333
where
@@ -337,10 +337,10 @@ pIntersectionWithKey xs ys = M.intersectionWithKey go (M.fromList xs) `eq_`
337337
------------------------------------------------------------------------
338338
-- ** Folds
339339

340-
pFoldr :: [(Int, Int)] -> Bool
340+
pFoldr :: [(Int, Int)] -> Property
341341
pFoldr = (List.sort . M.foldr (:) []) `eq` (List.sort . HM.foldr (:) [])
342342

343-
pFoldl :: [(Int, Int)] -> Bool
343+
pFoldl :: [(Int, Int)] -> Property
344344
pFoldl = (List.sort . M.foldl (flip (:)) []) `eq` (List.sort . HM.foldl (flip (:)) [])
345345

346346
pBifoldMap :: [(Int, Int)] -> Bool
@@ -358,52 +358,52 @@ pBifoldl xs = reverse (concatMap f $ HM.toList m) == bifoldl (flip (:)) (flip (:
358358
where f (k, v) = [k, v]
359359
m = HM.fromList xs
360360

361-
pFoldrWithKey :: [(Int, Int)] -> Bool
361+
pFoldrWithKey :: [(Int, Int)] -> Property
362362
pFoldrWithKey = (sortByKey . M.foldrWithKey f []) `eq`
363363
(sortByKey . HM.foldrWithKey f [])
364364
where f k v z = (k, v) : z
365365

366-
pFoldMapWithKey :: [(Int, Int)] -> Bool
366+
pFoldMapWithKey :: [(Int, Int)] -> Property
367367
pFoldMapWithKey = (sortByKey . M.foldMapWithKey f) `eq`
368368
(sortByKey . HM.foldMapWithKey f)
369369
where f k v = [(k, v)]
370370

371-
pFoldrWithKey' :: [(Int, Int)] -> Bool
371+
pFoldrWithKey' :: [(Int, Int)] -> Property
372372
pFoldrWithKey' = (sortByKey . M.foldrWithKey' f []) `eq`
373373
(sortByKey . HM.foldrWithKey' f [])
374374
where f k v z = (k, v) : z
375375

376-
pFoldlWithKey :: [(Int, Int)] -> Bool
376+
pFoldlWithKey :: [(Int, Int)] -> Property
377377
pFoldlWithKey = (sortByKey . M.foldlWithKey f []) `eq`
378378
(sortByKey . HM.foldlWithKey f [])
379379
where f z k v = (k, v) : z
380380

381-
pFoldlWithKey' :: [(Int, Int)] -> Bool
381+
pFoldlWithKey' :: [(Int, Int)] -> Property
382382
pFoldlWithKey' = (sortByKey . M.foldlWithKey' f []) `eq`
383383
(sortByKey . HM.foldlWithKey' f [])
384384
where f z k v = (k, v) : z
385385

386-
pFoldl' :: [(Int, Int)] -> Bool
386+
pFoldl' :: [(Int, Int)] -> Property
387387
pFoldl' = (List.sort . M.foldl' (flip (:)) []) `eq` (List.sort . HM.foldl' (flip (:)) [])
388388

389-
pFoldr' :: [(Int, Int)] -> Bool
389+
pFoldr' :: [(Int, Int)] -> Property
390390
pFoldr' = (List.sort . M.foldr' (:) []) `eq` (List.sort . HM.foldr' (:) [])
391391

392392
------------------------------------------------------------------------
393393
-- ** Filter
394394

395-
pMapMaybeWithKey :: [(Key, Int)] -> Bool
395+
pMapMaybeWithKey :: [(Key, Int)] -> Property
396396
pMapMaybeWithKey = M.mapMaybeWithKey f `eq_` HM.mapMaybeWithKey f
397397
where f k v = guard (odd (unK k + v)) >> Just (v + 1)
398398

399-
pMapMaybe :: [(Key, Int)] -> Bool
399+
pMapMaybe :: [(Key, Int)] -> Property
400400
pMapMaybe = M.mapMaybe f `eq_` HM.mapMaybe f
401401
where f v = guard (odd v) >> Just (v + 1)
402402

403-
pFilter :: [(Key, Int)] -> Bool
403+
pFilter :: [(Key, Int)] -> Property
404404
pFilter = M.filter odd `eq_` HM.filter odd
405405

406-
pFilterWithKey :: [(Key, Int)] -> Bool
406+
pFilterWithKey :: [(Key, Int)] -> Property
407407
pFilterWithKey = M.filterWithKey p `eq_` HM.filterWithKey p
408408
where p k v = odd (unK k + v)
409409

@@ -422,7 +422,7 @@ instance Hashable a => Hashable (Magma a) where
422422
hashWithSalt s (Op m n) = hashWithSalt s (hashWithSalt (hashWithSalt (2::Int) m) n)
423423

424424
-- 'eq_' already calls fromList.
425-
pFromList :: [(Key, Int)] -> Bool
425+
pFromList :: [(Key, Int)] -> Property
426426
pFromList = id `eq_` id
427427

428428
pFromListWith :: [(Key, Int)] -> Bool
@@ -436,13 +436,13 @@ pFromListWithKey kvs = (M.toAscList $ M.fromListWithKey combine kvsM) ==
436436
where kvsM = fmap (\(K k,v) -> (Leaf k, Leaf v)) kvs
437437
combine k v1 v2 = Op k (Op v1 v2)
438438

439-
pToList :: [(Key, Int)] -> Bool
439+
pToList :: [(Key, Int)] -> Property
440440
pToList = M.toAscList `eq` toAscList
441441

442-
pElems :: [(Key, Int)] -> Bool
442+
pElems :: [(Key, Int)] -> Property
443443
pElems = (List.sort . M.elems) `eq` (List.sort . HM.elems)
444444

445-
pKeys :: [(Key, Int)] -> Bool
445+
pKeys :: [(Key, Int)] -> Property
446446
pKeys = (List.sort . M.keys) `eq` (List.sort . HM.keys)
447447

448448
------------------------------------------------------------------------
@@ -561,24 +561,23 @@ type Model k v = M.Map k v
561561

562562
-- | Check that a function operating on a 'HashMap' is equivalent to
563563
-- one operating on a 'Model'.
564-
eq :: (Eq a, Eq k, Hashable k, Ord k)
564+
eq :: (Eq a, Eq k, Hashable k, Ord k, Show a, Show k)
565565
=> (Model k v -> a) -- ^ Function that modifies a 'Model'
566566
-> (HM.HashMap k v -> a) -- ^ Function that modified a 'HashMap' in the same
567567
-- way
568568
-> [(k, v)] -- ^ Initial content of the 'HashMap' and 'Model'
569-
-> Bool -- ^ True if the functions are equivalent
570-
eq f g xs = g (HM.fromList xs) == f (M.fromList xs)
569+
-> Property
570+
eq f g xs = g (HM.fromList xs) === f (M.fromList xs)
571571

572572
infix 4 `eq`
573573

574-
eq_ :: (Eq k, Eq v, Hashable k, Ord k)
574+
eq_ :: (Eq k, Eq v, Hashable k, Ord k, Show k, Show v)
575575
=> (Model k v -> Model k v) -- ^ Function that modifies a 'Model'
576576
-> (HM.HashMap k v -> HM.HashMap k v) -- ^ Function that modified a
577577
-- 'HashMap' in the same way
578578
-> [(k, v)] -- ^ Initial content of the 'HashMap'
579579
-- and 'Model'
580-
-> Bool -- ^ True if the functions are
581-
-- equivalent
580+
-> Property
582581
eq_ f g = (M.toAscList . f) `eq` (toAscList . g)
583582

584583
infix 4 `eq_`

0 commit comments

Comments
 (0)