Skip to content

Commit 8b4f520

Browse files
authored
Add symmetric difference ops (#1009)
...for Set, Map, IntSet, IntMap. This joins the set operations already implemented: union, intersection, difference.
1 parent e5661a7 commit 8b4f520

File tree

20 files changed

+247
-4
lines changed

20 files changed

+247
-4
lines changed

containers-tests/benchmarks/SetOperations/SetOperations-IntMap.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,10 @@ module Main where
33
import Data.IntMap as C
44
import SetOperations
55

6-
main = benchmark (\xs -> fromList [(x, x) | x <- xs]) True [("union", C.union), ("difference", C.difference), ("intersection", C.intersection)]
6+
main :: IO ()
7+
main = benchmark (\xs -> fromList [(x, x) | x <- xs]) True
8+
[ ("union", C.union)
9+
, ("difference", C.difference)
10+
, ("intersection", C.intersection)
11+
, ("symmetricDifference", C.symmetricDifference)
12+
]

containers-tests/benchmarks/SetOperations/SetOperations-IntSet.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,10 @@ module Main where
33
import Data.IntSet as C
44
import SetOperations
55

6-
main = benchmark fromList True [("union", C.union), ("difference", C.difference), ("intersection", C.intersection)]
6+
main :: IO ()
7+
main = benchmark fromList True
8+
[ ("union", C.union)
9+
, ("difference", C.difference)
10+
, ("intersection", C.intersection)
11+
, ("symmetricDifference", C.symmetricDifference)
12+
]

containers-tests/benchmarks/SetOperations/SetOperations-Map.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,10 @@ module Main where
33
import Data.Map as C
44
import SetOperations
55

6-
main = benchmark (\xs -> fromList [(x, x) | x <- xs]) True [("union", C.union), ("difference", C.difference), ("intersection", C.intersection)]
6+
main :: IO ()
7+
main = benchmark (\xs -> fromList [(x, x) | x <- xs]) True
8+
[ ("union", C.union)
9+
, ("difference", C.difference)
10+
, ("intersection", C.intersection)
11+
, ("symmetricDifference", C.symmetricDifference)
12+
]

containers-tests/benchmarks/SetOperations/SetOperations-Set.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,10 @@ module Main where
33
import Data.Set as C
44
import SetOperations
55

6-
main = benchmark fromList True [("union", C.union), ("difference", C.difference), ("intersection", C.intersection)]
6+
main :: IO ()
7+
main = benchmark fromList True
8+
[ ("union", C.union)
9+
, ("difference", C.difference)
10+
, ("intersection", C.intersection)
11+
, ("symmetricDifference", C.symmetricDifference)
12+
]

containers-tests/tests/intmap-properties.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,7 @@ main = defaultMain $ testGroup "intmap-properties"
150150
, testProperty "intersection model" prop_intersectionModel
151151
, testProperty "intersectionWith model" prop_intersectionWithModel
152152
, testProperty "intersectionWithKey model" prop_intersectionWithKeyModel
153+
, testProperty "symmetricDifference" prop_symmetricDifference
153154
, testProperty "mergeWithKey model" prop_mergeWithKeyModel
154155
, testProperty "merge valid" prop_merge_valid
155156
, testProperty "mergeA effects" prop_mergeA_effects
@@ -1258,6 +1259,17 @@ prop_intersectionWithKeyModel xs ys
12581259
ys' = List.nubBy ((==) `on` fst) ys
12591260
f k l r = k + 2 * l + 3 * r
12601261

1262+
prop_symmetricDifference :: IMap -> IMap -> Property
1263+
prop_symmetricDifference m1 m2 =
1264+
valid m3 .&&.
1265+
toAscList m3 ===
1266+
List.sort ( List.filter ((`notElem` fmap fst kys) . fst) kxs
1267+
++ List.filter ((`notElem` fmap fst kxs) . fst) kys)
1268+
where
1269+
m3 = symmetricDifference m1 m2
1270+
kxs = toAscList m1
1271+
kys = toAscList m2
1272+
12611273
prop_disjoint :: UMap -> UMap -> Property
12621274
prop_disjoint m1 m2 = disjoint m1 m2 === null (intersection m1 m2)
12631275

containers-tests/tests/intset-properties.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ main = defaultMain $ testGroup "intset-properties"
4242
, testProperty "prop_union" prop_union
4343
, testProperty "prop_difference" prop_difference
4444
, testProperty "prop_intersection" prop_intersection
45+
, testProperty "prop_symmetricDifference" prop_symmetricDifference
4546
, testProperty "prop_Ordered" prop_Ordered
4647
, testProperty "prop_List" prop_List
4748
, testProperty "prop_DescList" prop_DescList
@@ -264,6 +265,17 @@ prop_intersection xs ys =
264265
valid t .&&.
265266
toAscList t === (toAscList xs `List.intersect` toAscList ys)
266267

268+
prop_symmetricDifference :: IntSet -> IntSet -> Property
269+
prop_symmetricDifference xs ys =
270+
case symmetricDifference xs ys of
271+
t ->
272+
valid t .&&.
273+
toAscList t ===
274+
List.sort (List.filter (`notElem` xs') ys' ++ List.filter (`notElem` ys') xs')
275+
where
276+
xs' = toAscList xs
277+
ys' = toAscList ys
278+
267279
prop_disjoint :: IntSet -> IntSet -> Bool
268280
prop_disjoint a b = a `disjoint` b == null (a `intersection` b)
269281

containers-tests/tests/map-properties.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -178,6 +178,7 @@ main = defaultMain $ testGroup "map-properties"
178178
, testProperty "intersectionWithModel" prop_intersectionWithModel
179179
, testProperty "intersectionWithKey" prop_intersectionWithKey
180180
, testProperty "intersectionWithKeyModel" prop_intersectionWithKeyModel
181+
, testProperty "symmetricDifference" prop_symmetricDifference
181182
, testProperty "disjoint" prop_disjoint
182183
, testProperty "compose" prop_compose
183184
, testProperty "differenceMerge" prop_differenceMerge
@@ -1168,6 +1169,17 @@ prop_intersectionWithKeyModel xs ys
11681169
ys' = List.nubBy ((==) `on` fst) ys
11691170
f k l r = k + 2 * l + 3 * r
11701171

1172+
prop_symmetricDifference :: IMap -> IMap -> Property
1173+
prop_symmetricDifference m1 m2 =
1174+
valid m3 .&&.
1175+
toAscList m3 ===
1176+
List.sort ( List.filter ((`notElem` fmap fst kys) . fst) kxs
1177+
++ List.filter ((`notElem` fmap fst kxs) . fst) kys)
1178+
where
1179+
m3 = symmetricDifference m1 m2
1180+
kxs = toAscList m1
1181+
kys = toAscList m2
1182+
11711183
prop_disjoint :: UMap -> UMap -> Property
11721184
prop_disjoint m1 m2 = disjoint m1 m2 === null (intersection m1 m2)
11731185

containers-tests/tests/set-properties.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,7 @@ main = defaultMain $ testGroup "set-properties"
7474
, testProperty "prop_isProperSubsetOf2" prop_isProperSubsetOf2
7575
, testProperty "prop_isSubsetOf" prop_isSubsetOf
7676
, testProperty "prop_isSubsetOf2" prop_isSubsetOf2
77+
, testProperty "prop_symmetricDifference" prop_symmetricDifference
7778
, testProperty "prop_disjoint" prop_disjoint
7879
, testProperty "prop_size" prop_size
7980
, testProperty "prop_lookupMax" prop_lookupMax
@@ -487,6 +488,16 @@ prop_Int :: [Int] -> [Int] -> Bool
487488
prop_Int xs ys = toAscList (intersection (fromList xs) (fromList ys))
488489
== List.sort (nub ((List.intersect) (xs) (ys)))
489490

491+
prop_symmetricDifference :: Set Int -> Set Int -> Property
492+
prop_symmetricDifference xs ys =
493+
valid zs .&&.
494+
toAscList zs ===
495+
List.sort (List.filter (`notElem` xs') ys' ++ List.filter (`notElem` ys') xs')
496+
where
497+
zs = symmetricDifference xs ys
498+
xs' = toAscList xs
499+
ys' = toAscList ys
500+
490501
prop_disjoint :: Set Int -> Set Int -> Bool
491502
prop_disjoint a b = a `disjoint` b == null (a `intersection` b)
492503

containers/src/Data/IntMap/Internal.hs

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -125,6 +125,9 @@ module Data.IntMap.Internal (
125125
, intersectionWith
126126
, intersectionWithKey
127127

128+
-- ** Symmetric difference
129+
, symmetricDifference
130+
128131
-- ** Compose
129132
, compose
130133

@@ -1304,6 +1307,49 @@ intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
13041307
intersectionWithKey f m1 m2
13051308
= mergeWithKey' bin (\(Tip k1 x1) (Tip _k2 x2) -> Tip k1 (f k1 x1 x2)) (const Nil) (const Nil) m1 m2
13061309

1310+
{--------------------------------------------------------------------
1311+
Symmetric difference
1312+
--------------------------------------------------------------------}
1313+
1314+
-- | \(O(n+m)\). The symmetric difference of two maps.
1315+
--
1316+
-- The result contains entries whose keys appear in exactly one of the two maps.
1317+
--
1318+
-- @
1319+
-- symmetricDifference
1320+
-- (fromList [(0,\'q\'),(2,\'b\'),(4,\'w\'),(6,\'o\')])
1321+
-- (fromList [(0,\'e\'),(3,\'r\'),(6,\'t\'),(9,\'s\')])
1322+
-- ==
1323+
-- fromList [(2,\'b\'),(3,\'r\'),(4,\'w\'),(9,\'s\')]
1324+
-- @
1325+
--
1326+
-- @since FIXME
1327+
symmetricDifference :: IntMap a -> IntMap a -> IntMap a
1328+
symmetricDifference t1@(Bin p1 l1 r1) t2@(Bin p2 l2 r2) =
1329+
case treeTreeBranch p1 p2 of
1330+
ABL -> bin p1 (symmetricDifference l1 t2) r1
1331+
ABR -> bin p1 l1 (symmetricDifference r1 t2)
1332+
BAL -> bin p2 (symmetricDifference t1 l2) r2
1333+
BAR -> bin p2 l2 (symmetricDifference t1 r2)
1334+
EQL -> bin p1 (symmetricDifference l1 l2) (symmetricDifference r1 r2)
1335+
NOM -> link (unPrefix p1) t1 (unPrefix p2) t2
1336+
symmetricDifference t1@(Bin _ _ _) t2@(Tip k2 _) = symDiffTip t2 k2 t1
1337+
symmetricDifference t1@(Bin _ _ _) Nil = t1
1338+
symmetricDifference t1@(Tip k1 _) t2 = symDiffTip t1 k1 t2
1339+
symmetricDifference Nil t2 = t2
1340+
1341+
symDiffTip :: IntMap a -> Int -> IntMap a -> IntMap a
1342+
symDiffTip !t1 !k1 = go
1343+
where
1344+
go t2@(Bin p2 l2 r2)
1345+
| nomatch k1 p2 = linkKey k1 t1 p2 t2
1346+
| left k1 p2 = bin p2 (go l2) r2
1347+
| otherwise = bin p2 l2 (go r2)
1348+
go t2@(Tip k2 _)
1349+
| k1 == k2 = Nil
1350+
| otherwise = link k1 t1 k2 t2
1351+
go Nil = t1
1352+
13071353
{--------------------------------------------------------------------
13081354
MergeWithKey
13091355
--------------------------------------------------------------------}

containers/src/Data/IntMap/Lazy.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,9 @@ module Data.IntMap.Lazy (
142142
, intersectionWith
143143
, intersectionWithKey
144144

145+
-- ** Symmetric difference
146+
, symmetricDifference
147+
145148
-- ** Disjoint
146149
, disjoint
147150

0 commit comments

Comments
 (0)