Skip to content

Commit 6ae0580

Browse files
authored
Remove redundant Hashable constraints from intersection.*, union.* (#478)
Closes #443.
1 parent 087ba87 commit 6ae0580

File tree

3 files changed

+14
-14
lines changed

3 files changed

+14
-14
lines changed

Data/HashMap/Internal.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1582,22 +1582,22 @@ submapBitmapIndexed comp !b1 !ary1 !b2 !ary2 = subsetBitmaps && go 0 0 (b1Orb2 .
15821582
--
15831583
-- >>> union (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
15841584
-- fromList [(1,'a'),(2,'b'),(3,'d')]
1585-
union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v
1585+
union :: Eq k => HashMap k v -> HashMap k v -> HashMap k v
15861586
union = unionWith const
15871587
{-# INLINABLE union #-}
15881588

15891589
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
15901590
-- the provided function (first argument) will be used to compute the
15911591
-- result.
1592-
unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v
1592+
unionWith :: Eq k => (v -> v -> v) -> HashMap k v -> HashMap k v
15931593
-> HashMap k v
15941594
unionWith f = unionWithKey (const f)
15951595
{-# INLINE unionWith #-}
15961596

15971597
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
15981598
-- the provided function (first argument) will be used to compute the
15991599
-- result.
1600-
unionWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> HashMap k v -> HashMap k v
1600+
unionWithKey :: Eq k => (k -> v -> v -> v) -> HashMap k v -> HashMap k v
16011601
-> HashMap k v
16021602
unionWithKey f = go 0
16031603
where
@@ -1718,7 +1718,7 @@ unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
17181718
-- TODO: Figure out the time complexity of 'unions'.
17191719

17201720
-- | Construct a set containing all elements from a list of sets.
1721-
unions :: (Eq k, Hashable k) => [HashMap k v] -> HashMap k v
1721+
unions :: Eq k => [HashMap k v] -> HashMap k v
17221722
unions = List.foldl' union empty
17231723
{-# INLINE unions #-}
17241724

@@ -1833,21 +1833,21 @@ differenceWith f a b = foldlWithKey' go empty a
18331833

18341834
-- | \(O(n \log m)\) Intersection of two maps. Return elements of the first
18351835
-- map for keys existing in the second.
1836-
intersection :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v
1836+
intersection :: Eq k => HashMap k v -> HashMap k w -> HashMap k v
18371837
intersection = Exts.inline intersectionWith const
18381838
{-# INLINABLE intersection #-}
18391839

18401840
-- | \(O(n \log m)\) Intersection of two maps. If a key occurs in both maps
18411841
-- the provided function is used to combine the values from the two
18421842
-- maps.
1843-
intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
1843+
intersectionWith :: Eq k => (v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
18441844
intersectionWith f = Exts.inline intersectionWithKey $ const f
18451845
{-# INLINABLE intersectionWith #-}
18461846

18471847
-- | \(O(n \log m)\) Intersection of two maps. If a key occurs in both maps
18481848
-- the provided function is used to combine the values from the two
18491849
-- maps.
1850-
intersectionWithKey :: (Eq k, Hashable k) => (k -> v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
1850+
intersectionWithKey :: Eq k => (k -> v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
18511851
intersectionWithKey f = intersectionWithKey# $ \k v1 v2 -> (# f k v1 v2 #)
18521852
{-# INLINABLE intersectionWithKey #-}
18531853

Data/HashMap/Internal/Strict.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -446,14 +446,14 @@ alterFEager f !k !m = (<$> f mv) $ \fres ->
446446

447447
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
448448
-- the provided function (first argument) will be used to compute the result.
449-
unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v
449+
unionWith :: Eq k => (v -> v -> v) -> HashMap k v -> HashMap k v
450450
-> HashMap k v
451451
unionWith f = unionWithKey (const f)
452452
{-# INLINE unionWith #-}
453453

454454
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
455455
-- the provided function (first argument) will be used to compute the result.
456-
unionWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> HashMap k v -> HashMap k v
456+
unionWithKey :: Eq k => (k -> v -> v -> v) -> HashMap k v -> HashMap k v
457457
-> HashMap k v
458458
unionWithKey f = go 0
459459
where
@@ -622,15 +622,15 @@ differenceWith f a b = HM.foldlWithKey' go HM.empty a
622622
-- | \(O(n+m)\) Intersection of two maps. If a key occurs in both maps
623623
-- the provided function is used to combine the values from the two
624624
-- maps.
625-
intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1
625+
intersectionWith :: Eq k => (v1 -> v2 -> v3) -> HashMap k v1
626626
-> HashMap k v2 -> HashMap k v3
627627
intersectionWith f = Exts.inline intersectionWithKey $ const f
628628
{-# INLINABLE intersectionWith #-}
629629

630630
-- | \(O(n+m)\) Intersection of two maps. If a key occurs in both maps
631631
-- the provided function is used to combine the values from the two
632632
-- maps.
633-
intersectionWithKey :: (Eq k, Hashable k) => (k -> v1 -> v2 -> v3)
633+
intersectionWithKey :: Eq k => (k -> v1 -> v2 -> v3)
634634
-> HashMap k v1 -> HashMap k v2 -> HashMap k v3
635635
intersectionWithKey f = HM.intersectionWithKey# $ \k v1 v2 -> let !v3 = f k v1 v2 in (# v3 #)
636636
{-# INLINABLE intersectionWithKey #-}

Data/HashSet/Internal.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -306,14 +306,14 @@ isSubsetOf s1 s2 = H.isSubmapOfBy (\_ _ -> True) (asMap s1) (asMap s2)
306306
--
307307
-- >>> union (fromList [1,2]) (fromList [2,3])
308308
-- fromList [1,2,3]
309-
union :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
309+
union :: Eq a => HashSet a -> HashSet a -> HashSet a
310310
union s1 s2 = HashSet $ H.union (asMap s1) (asMap s2)
311311
{-# INLINE union #-}
312312

313313
-- TODO: Figure out the time complexity of 'unions'.
314314

315315
-- | Construct a set containing all elements from a list of sets.
316-
unions :: (Eq a, Hashable a) => [HashSet a] -> HashSet a
316+
unions :: Eq a => [HashSet a] -> HashSet a
317317
unions = List.foldl' union empty
318318
{-# INLINE unions #-}
319319

@@ -391,7 +391,7 @@ difference (HashSet a) (HashSet b) = HashSet (H.difference a b)
391391
--
392392
-- >>> HashSet.intersection (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
393393
-- fromList [2,3]
394-
intersection :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
394+
intersection :: Eq a => HashSet a -> HashSet a -> HashSet a
395395
intersection (HashSet a) (HashSet b) = HashSet (H.intersection a b)
396396
{-# INLINABLE intersection #-}
397397

0 commit comments

Comments
 (0)