From 83d113059e201688e4b7e38a787036efb59b5c8e Mon Sep 17 00:00:00 2001 From: Simon Jakobi Date: Wed, 26 Nov 2025 20:45:00 +0100 Subject: [PATCH] Remove redundant `Eq` constraints `Eq` has been a superclass of `Hashable` since `hashable-1.4`, which is the minimum version u-c supports. --- Data/HashMap/Internal.hs | 68 ++++++++++++++++----------------- Data/HashMap/Internal/Strict.hs | 28 +++++++------- Data/HashSet/Internal.hs | 26 ++++++------- benchmarks/Benchmarks.hs | 22 +++++------ tests/Properties/HashMapLazy.hs | 4 +- tests/Properties/HashSet.hs | 4 +- tests/Strictness.hs | 2 +- 7 files changed, 77 insertions(+), 77 deletions(-) diff --git a/Data/HashMap/Internal.hs b/Data/HashMap/Internal.hs index 886ead2a..2850e680 100644 --- a/Data/HashMap/Internal.hs +++ b/Data/HashMap/Internal.hs @@ -311,7 +311,7 @@ instance Bifoldable HashMap where -- -- >>> fromList [(1,'a'),(2,'b')] <> fromList [(2,'c'),(3,'d')] -- fromList [(1,'a'),(2,'b'),(3,'d')] -instance (Eq k, Hashable k) => Semigroup (HashMap k v) where +instance Hashable k => Semigroup (HashMap k v) where (<>) = union {-# INLINE (<>) #-} stimes = stimesIdempotentMonoid @@ -327,13 +327,13 @@ instance (Eq k, Hashable k) => Semigroup (HashMap k v) where -- -- >>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')]) -- fromList [(1,'a'),(2,'b'),(3,'d')] -instance (Eq k, Hashable k) => Monoid (HashMap k v) where +instance Hashable k => Monoid (HashMap k v) where mempty = empty {-# INLINE mempty #-} mappend = (<>) {-# INLINE mappend #-} -instance (Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) where +instance (Data k, Data v, Hashable k) => Data (HashMap k v) where gfoldl f z m = z fromList `f` toList m toConstr _ = fromListConstr gunfold k z c = case Data.constrIndex c of @@ -376,14 +376,14 @@ instance Show2 HashMap where instance Show k => Show1 (HashMap k) where liftShowsPrec = liftShowsPrec2 showsPrec showList -instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where +instance (Hashable k, Read k) => Read1 (HashMap k) where liftReadsPrec rp rl = FC.readsData $ FC.readsUnaryWith (liftReadsPrec rp' rl') "fromList" fromList where rp' = liftReadsPrec rp rl rl' = liftReadList rp rl -instance (Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) where +instance (Hashable k, Read k, Read e) => Read (HashMap k e) where readPrec = parens $ prec 10 $ do Ident "fromList" <- lexP fromList <$> readPrec @@ -624,7 +624,7 @@ size t = go t 0 -- | \(O(\log n)\) Return 'True' if the specified key is present in the -- map, 'False' otherwise. -member :: (Eq k, Hashable k) => k -> HashMap k a -> Bool +member :: Hashable k => k -> HashMap k a -> Bool member k m = case lookup k m of Nothing -> False Just _ -> True @@ -632,7 +632,7 @@ member k m = case lookup k m of -- | \(O(\log n)\) Return the value to which the specified key is mapped, -- or 'Nothing' if this map contains no mapping for the key. -lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v +lookup :: Hashable k => k -> HashMap k v -> Maybe v -- GHC does not yet perform a worker-wrapper transformation on -- unboxed sums automatically. That seems likely to happen at some -- point (possibly as early as GHC 8.6) but for now we do it manually. @@ -641,7 +641,7 @@ lookup k m = case lookup# k m of (# | a #) -> Just a {-# INLINE lookup #-} -lookup# :: (Eq k, Hashable k) => k -> HashMap k v -> (# (# #) | v #) +lookup# :: Hashable k => k -> HashMap k v -> (# (# #) | v #) lookup# k m = lookupCont (\_ -> (# (# #) | #)) (\v _i -> (# | v #)) (hash k) k 0 m {-# INLINABLE lookup# #-} @@ -746,7 +746,7 @@ lookupCont absent present !h0 !k0 !s0 m0 = go h0 k0 s0 m0 -- This is a flipped version of 'lookup'. -- -- @since 0.2.11 -(!?) :: (Eq k, Hashable k) => HashMap k v -> k -> Maybe v +(!?) :: Hashable k => HashMap k v -> k -> Maybe v (!?) m k = lookup k m {-# INLINE (!?) #-} @@ -755,7 +755,7 @@ lookupCont absent present !h0 !k0 !s0 m0 = go h0 k0 s0 m0 -- or the default value if this map contains no mapping for the key. -- -- @since 0.2.11 -findWithDefault :: (Eq k, Hashable k) +findWithDefault :: Hashable k => v -- ^ Default value to return. -> k -> HashMap k v -> v findWithDefault def k t = case lookup k t of @@ -769,7 +769,7 @@ findWithDefault def k t = case lookup k t of -- -- DEPRECATED: lookupDefault is deprecated as of version 0.2.11, replaced -- by 'findWithDefault'. -lookupDefault :: (Eq k, Hashable k) +lookupDefault :: Hashable k => v -- ^ Default value to return. -> k -> HashMap k v -> v lookupDefault = findWithDefault @@ -777,7 +777,7 @@ lookupDefault = findWithDefault -- | \(O(\log n)\) Return the value to which the specified key is mapped. -- Calls 'error' if this map contains no mapping for the key. -(!) :: (Eq k, Hashable k, HasCallStack) => HashMap k v -> k -> v +(!) :: (Hashable k, HasCallStack) => HashMap k v -> k -> v (!) m k = case lookup k m of Just v -> v Nothing -> error "Data.HashMap.Internal.(!): key not found" @@ -841,7 +841,7 @@ bitmapIndexedOrFull b !ary -- | \(O(\log n)\) Associate the specified value with the specified -- key in this map. If this map previously contained a mapping for -- the key, the old value is replaced. -insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v +insert :: Hashable k => k -> v -> HashMap k v -> HashMap k v insert k v m = insert' (hash k) k v m {-# INLINABLE insert #-} @@ -959,7 +959,7 @@ setAtPosition i k x ary = A.update ary i (L k x) -- | In-place update version of insert -unsafeInsert :: forall k v. (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v +unsafeInsert :: forall k v. Hashable k => k -> v -> HashMap k v -> HashMap k v unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0) where h0 = hash k0 @@ -1036,7 +1036,7 @@ two = go -- -- > insertWith f k v map -- > where f new old = new + old -insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v +insertWith :: Hashable k => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v -- We're not going to worry about allocating a function closure -- to pass to insertModifying. See comments at 'adjust'. @@ -1048,7 +1048,7 @@ insertWith f k new m = insertModifying new (\old -> (# f new old #)) k m -- to apply to calculate a new value when the key is present. Thanks -- to the unboxed unary tuple, we avoid introducing any unnecessary -- thunks in the tree. -insertModifying :: (Eq k, Hashable k) => v -> (v -> (# v #)) -> k -> HashMap k v +insertModifying :: Hashable k => v -> (v -> (# v #)) -> k -> HashMap k v -> HashMap k v insertModifying x f k0 m0 = go h0 k0 0 m0 where @@ -1112,13 +1112,13 @@ insertModifyingArr x f k0 ary0 = go k0 ary0 0 (A.length ary0) {-# INLINE insertModifyingArr #-} -- | In-place update version of insertWith -unsafeInsertWith :: forall k v. (Eq k, Hashable k) +unsafeInsertWith :: forall k v. Hashable k => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v unsafeInsertWith f k0 v0 m0 = unsafeInsertWithKey (\_ a b -> (# f a b #)) k0 v0 m0 {-# INLINABLE unsafeInsertWith #-} -unsafeInsertWithKey :: forall k v. (Eq k, Hashable k) +unsafeInsertWithKey :: forall k v. Hashable k => (k -> v -> v -> (# v #)) -> k -> v -> HashMap k v -> HashMap k v unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) @@ -1156,7 +1156,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) -- | \(O(\log n)\) Remove the mapping for the specified key from this map -- if present. -delete :: (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v +delete :: Hashable k => k -> HashMap k v -> HashMap k v delete k m = delete' (hash k) k m {-# INLINABLE delete #-} @@ -1251,7 +1251,7 @@ deleteKeyExists !collPos0 !h0 !k0 m0 = go collPos0 h0 k0 m0 -- | \(O(\log n)\) Adjust the value tied to a given key in this map only -- if it is present. Otherwise, leave the map alone. -adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v +adjust :: Hashable k => (v -> v) -> k -> HashMap k v -> HashMap k v -- This operation really likes to leak memory, so using this -- indirect implementation shouldn't hurt much. Furthermore, it allows -- GHC to avoid a leak when the function is lazy. In particular, @@ -1263,7 +1263,7 @@ adjust f k m = adjust# (\v -> (# f v #)) k m {-# INLINE adjust #-} -- | Much like 'adjust', but not inherently leaky. -adjust# :: (Eq k, Hashable k) => (v -> (# v #)) -> k -> HashMap k v -> HashMap k v +adjust# :: Hashable k => (v -> (# v #)) -> k -> HashMap k v -> HashMap k v adjust# f k0 m0 = go h0 k0 0 m0 where h0 = hash k0 @@ -1305,7 +1305,7 @@ adjust# f k0 m0 = go h0 k0 0 m0 -- | \(O(\log n)\) The expression @('update' f k map)@ updates the value @x@ at @k@ -- (if it is in the map). If @(f x)@ is 'Nothing', the element is deleted. -- If it is @('Just' y)@, the key @k@ is bound to the new value @y@. -update :: (Eq k, Hashable k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a +update :: Hashable k => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a update f = alter (>>= f) {-# INLINABLE update #-} @@ -1318,7 +1318,7 @@ update f = alter (>>= f) -- @ -- 'lookup' k ('alter' f k m) = f ('lookup' k m) -- @ -alter :: (Eq k, Hashable k) => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v +alter :: Hashable k => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v alter f k m = let !h = hash k !lookupRes = lookupRecordCollision h k m @@ -1343,7 +1343,7 @@ alter f k m = -- . -- -- @since 0.2.10 -alterF :: (Functor f, Eq k, Hashable k) +alterF :: (Functor f, Hashable k) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) -- We only calculate the hash once, but unless this is rewritten -- by rules we may test for key equality multiple times. @@ -1433,7 +1433,7 @@ bogus# _ = error "Data.HashMap.alterF internal error: hit bogus#" -- -- Failure to abide by these laws will make demons come out of your nose. alterFWeird - :: (Functor f, Eq k, Hashable k) + :: (Functor f, Hashable k) => f (Maybe v) -> f (Maybe v) -> (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) @@ -1443,7 +1443,7 @@ alterFWeird _ _ f = alterFEager f -- | This is the default version of alterF that we use in most non-trivial -- cases. It's called "eager" because it looks up the given key in the map -- eagerly, whether or not the given function requires that information. -alterFEager :: (Functor f, Eq k, Hashable k) +alterFEager :: (Functor f, Hashable k) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) alterFEager f !k m = (<$> f mv) $ \case @@ -1492,7 +1492,7 @@ alterFEager f !k m = (<$> f mv) $ \case -- False -- -- @since 0.2.12 -isSubmapOf :: (Eq k, Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool +isSubmapOf :: (Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool isSubmapOf = Exts.inline isSubmapOfBy (==) {-# INLINABLE isSubmapOf #-} @@ -1512,7 +1512,7 @@ isSubmapOf = Exts.inline isSubmapOfBy (==) -- False -- -- @since 0.2.12 -isSubmapOfBy :: (Eq k, Hashable k) => (v1 -> v2 -> Bool) -> HashMap k v1 -> HashMap k v2 -> Bool +isSubmapOfBy :: Hashable k => (v1 -> v2 -> Bool) -> HashMap k v1 -> HashMap k v2 -> Bool -- For maps without collisions the complexity is O(n*log m), where n is the size -- of m1 and m the size of m2: the inclusion operation visits every leaf in m1 at least once. -- For each leaf in m1, it looks up the key in m2. @@ -1766,7 +1766,7 @@ unions = List.foldl' union empty -- @ -- -- @since 0.2.13.0 -compose :: (Eq b, Hashable b) => HashMap b c -> HashMap a b -> HashMap a c +compose :: Hashable b => HashMap b c -> HashMap a b -> HashMap a c compose bc !ab | null bc = empty | otherwise = mapMaybe (bc !?) ab @@ -1829,7 +1829,7 @@ traverseWithKey f = go -- fromList [(3,"c")] -- -- @since 0.2.14.0 -mapKeys :: (Eq k2, Hashable k2) => (k1 -> k2) -> HashMap k1 v -> HashMap k2 v +mapKeys :: Hashable k2 => (k1 -> k2) -> HashMap k1 v -> HashMap k2 v mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) [] ------------------------------------------------------------------------ @@ -2559,7 +2559,7 @@ toList t = Exts.build (\ c z -> foldrWithKey (curry c) z t) -- | \(O(n \log n)\) Construct a map with the supplied mappings. If the list -- contains duplicate mappings, the later mappings take precedence. -fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v +fromList :: Hashable k => [(k, v)] -> HashMap k v fromList = List.foldl' (\ m (k, v) -> unsafeInsert k v m) empty {-# INLINABLE fromList #-} @@ -2593,7 +2593,7 @@ fromList = List.foldl' (\ m (k, v) -> unsafeInsert k v m) empty -- -- > fromListWith f [(k, a), (k, b), (k, c), (k, d)] -- > = fromList [(k, f d (f c (f b a)))] -fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v +fromListWith :: Hashable k => (v -> v -> v) -> [(k, v)] -> HashMap k v fromListWith f = List.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty {-# INLINE fromListWith #-} @@ -2623,7 +2623,7 @@ fromListWith f = List.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty -- > = fromList [(k, f k d (f k c (f k b a)))] -- -- @since 0.2.11 -fromListWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v +fromListWithKey :: Hashable k => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v fromListWithKey f = List.foldl' (\ m (k, v) -> unsafeInsertWithKey (\k' a b -> (# f k' a b #)) k v m) empty {-# INLINE fromListWithKey #-} @@ -2893,7 +2893,7 @@ otherOfOneOrZero i = 1 - i #if defined(__GLASGOW_HASKELL__) ------------------------------------------------------------------------ -- IsList instance -instance (Eq k, Hashable k) => Exts.IsList (HashMap k v) where +instance Hashable k => Exts.IsList (HashMap k v) where type Item (HashMap k v) = (k, v) fromList = fromList toList = toList diff --git a/Data/HashMap/Internal/Strict.hs b/Data/HashMap/Internal/Strict.hs index 6951fa3b..6fab7540 100644 --- a/Data/HashMap/Internal/Strict.hs +++ b/Data/HashMap/Internal/Strict.hs @@ -178,7 +178,7 @@ singleton k !v = HM.singleton k v -- | \(O(\log n)\) Associate the specified value with the specified -- key in this map. If this map previously contained a mapping for -- the key, the old value is replaced. -insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v +insert :: Hashable k => k -> v -> HashMap k v -> HashMap k v insert k !v = HM.insert k v {-# INLINABLE insert #-} @@ -189,7 +189,7 @@ insert k !v = HM.insert k v -- -- > insertWith f k v map -- > where f new old = new + old -insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v +insertWith :: Hashable k => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v insertWith f k0 v0 m0 = go h0 k0 v0 0 m0 where @@ -225,12 +225,12 @@ insertWith f k0 v0 m0 = go h0 k0 v0 0 m0 {-# INLINABLE insertWith #-} -- | In-place update version of insertWith -unsafeInsertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v +unsafeInsertWith :: Hashable k => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v unsafeInsertWith f k0 v0 m0 = unsafeInsertWithKey (const f) k0 v0 m0 {-# INLINABLE unsafeInsertWith #-} -unsafeInsertWithKey :: forall k v. (Eq k, Hashable k) => (k -> v -> v -> v) -> k -> v -> HashMap k v +unsafeInsertWithKey :: forall k v. Hashable k => (k -> v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) where @@ -268,7 +268,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) -- | \(O(\log n)\) Adjust the value tied to a given key in this map only -- if it is present. Otherwise, leave the map alone. -adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v +adjust :: Hashable k => (v -> v) -> k -> HashMap k v -> HashMap k v adjust f k0 m0 = go h0 k0 0 m0 where h0 = hash k0 @@ -301,7 +301,7 @@ adjust f k0 m0 = go h0 k0 0 m0 -- | \(O(\log n)\) The expression @('update' f k map)@ updates the value @x@ at @k@ -- (if it is in the map). If @(f x)@ is 'Nothing', the element is deleted. -- If it is @('Just' y)@, the key @k@ is bound to the new value @y@. -update :: (Eq k, Hashable k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a +update :: Hashable k => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a update f = alter (>>= f) {-# INLINABLE update #-} @@ -313,7 +313,7 @@ update f = alter (>>= f) -- @ -- 'lookup' k ('alter' f k m) = f ('lookup' k m) -- @ -alter :: (Eq k, Hashable k) => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v +alter :: Hashable k => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v alter f k m = let !h = hash k !lookupRes = HM.lookupRecordCollision h k m @@ -338,7 +338,7 @@ alter f k m = -- . -- -- @since 0.2.10 -alterF :: (Functor f, Eq k, Hashable k) +alterF :: (Functor f, Hashable k) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) -- Special care is taken to only calculate the hash once. When we rewrite -- with RULES, we also ensure that we only compare the key for equality @@ -405,7 +405,7 @@ impossibleAdjust = error "Data.HashMap.alterF internal error: impossible adjust" -- -- Failure to abide by these laws will make demons come out of your nose. alterFWeird - :: (Functor f, Eq k, Hashable k) + :: (Functor f, Hashable k) => f (Maybe v) -> f (Maybe v) -> (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) @@ -415,7 +415,7 @@ alterFWeird _ _ f = alterFEager f -- | This is the default version of alterF that we use in most non-trivial -- cases. It's called "eager" because it looks up the given key in the map -- eagerly, whether or not the given function requires that information. -alterFEager :: (Functor f, Eq k, Hashable k) +alterFEager :: (Functor f, Hashable k) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) alterFEager f !k !m = (<$> f mv) $ \fres -> case fres of @@ -620,7 +620,7 @@ traverseWithKey f = go -- encountered, the combining function is applied to the values of these keys. -- If it returns 'Nothing', the element is discarded (proper set difference). If -- it returns (@'Just' y@), the element is updated with a new value @y@. -differenceWith :: (Eq k, Hashable k) => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v +differenceWith :: Hashable k => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v differenceWith f = HM.differenceWithKey $ \_k vA vB -> case f vA vB of Nothing -> Nothing @@ -660,7 +660,7 @@ intersectionWithKey f = HM.intersectionWithKey# $ \k v1 v2 -> let !v3 = f k v1 v -- | \(O(n \log n)\) Construct a map with the supplied mappings. If the -- list contains duplicate mappings, the later mappings take -- precedence. -fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v +fromList :: Hashable k => [(k, v)] -> HashMap k v fromList = List.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) HM.empty {-# INLINABLE fromList #-} @@ -694,7 +694,7 @@ fromList = List.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) HM.empty -- -- > fromListWith f [(k, a), (k, b), (k, c), (k, d)] -- > = fromList [(k, f d (f c (f b a)))] -fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v +fromListWith :: Hashable k => (v -> v -> v) -> [(k, v)] -> HashMap k v fromListWith f = List.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) HM.empty {-# INLINE fromListWith #-} @@ -724,7 +724,7 @@ fromListWith f = List.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) HM.empty -- > = fromList [(k, f k d (f k c (f k b a)))] -- -- @since 0.2.11 -fromListWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v +fromListWithKey :: Hashable k => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v fromListWithKey f = List.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) HM.empty {-# INLINE fromListWithKey #-} diff --git a/Data/HashSet/Internal.hs b/Data/HashSet/Internal.hs index 671c680f..aa0e2fbf 100644 --- a/Data/HashSet/Internal.hs +++ b/Data/HashSet/Internal.hs @@ -145,7 +145,7 @@ instance NFData1 HashSet where -- -- In general, the lack of extensionality can be observed with any function -- that depends on the key ordering, such as folds and traversals. -instance (Eq a) => Eq (HashSet a) where +instance Eq a => Eq (HashSet a) where HashSet a == HashSet b = equalKeys a b {-# INLINE (==) #-} @@ -187,7 +187,7 @@ instance Foldable.Foldable HashSet where -- -- >>> fromList [1,2] <> fromList [2,3] -- fromList [1,2,3] -instance (Hashable a, Eq a) => Semigroup (HashSet a) where +instance Hashable a => Semigroup (HashSet a) where (<>) = union {-# INLINE (<>) #-} stimes = stimesIdempotentMonoid @@ -206,13 +206,13 @@ instance (Hashable a, Eq a) => Semigroup (HashSet a) where -- -- >>> mappend (fromList [1,2]) (fromList [2,3]) -- fromList [1,2,3] -instance (Hashable a, Eq a) => Monoid (HashSet a) where +instance Hashable a => Monoid (HashSet a) where mempty = empty {-# INLINE mempty #-} mappend = (<>) {-# INLINE mappend #-} -instance (Eq a, Hashable a, Read a) => Read (HashSet a) where +instance (Hashable a, Read a) => Read (HashSet a) where readPrec = parens $ prec 10 $ do Ident "fromList" <- lexP fromList <$> readPrec @@ -227,7 +227,7 @@ instance (Show a) => Show (HashSet a) where showsPrec d m = showParen (d > 10) $ showString "fromList " . shows (toList m) -instance (Data a, Eq a, Hashable a) => Data (HashSet a) where +instance (Data a, Hashable a) => Data (HashSet a) where gfoldl f z m = z fromList `f` toList m toConstr _ = fromListConstr gunfold k z c = case Data.constrIndex c of @@ -297,7 +297,7 @@ keysSet m = fromMap (() <$ m) -- False -- -- @since 0.2.12 -isSubsetOf :: (Eq a, Hashable a) => HashSet a -> HashSet a -> Bool +isSubsetOf :: Hashable a => HashSet a -> HashSet a -> Bool isSubsetOf s1 s2 = H.isSubmapOfBy (\_ _ -> True) (asMap s1) (asMap s2) -- | \(O(n+m)\) Construct a set containing all elements from both sets. @@ -345,7 +345,7 @@ size = H.size . asMap -- True -- >>> HashSet.member 1 (Hashset.fromList [4,5,6]) -- False -member :: (Eq a, Hashable a) => a -> HashSet a -> Bool +member :: Hashable a => a -> HashSet a -> Bool member a s = case H.lookup a (asMap s) of Just _ -> True _ -> False @@ -363,7 +363,7 @@ lookupElement a = H.lookupKey a . asMap -- -- >>> HashSet.insert 1 HashSet.empty -- fromList [1] -insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a +insert :: Hashable a => a -> HashSet a -> HashSet a insert a = HashSet . H.insert a () . asMap {-# INLINABLE insert #-} @@ -373,7 +373,7 @@ insert a = HashSet . H.insert a () . asMap -- fromList [2,3] -- >>> HashSet.delete 1 (HashSet.fromList [4,5,6]) -- fromList [4,5,6] -delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a +delete :: Hashable a => a -> HashSet a -> HashSet a delete a = HashSet . H.delete a . asMap {-# INLINABLE delete #-} @@ -382,7 +382,7 @@ delete a = HashSet . H.delete a . asMap -- -- >>> HashSet.map show (HashSet.fromList [1,2,3]) -- HashSet.fromList ["1","2","3"] -map :: (Hashable b, Eq b) => (a -> b) -> HashSet a -> HashSet b +map :: Hashable b => (a -> b) -> HashSet a -> HashSet b map f = fromList . List.map f . toList {-# INLINE map #-} @@ -391,7 +391,7 @@ map f = fromList . List.map f . toList -- -- >>> HashSet.difference (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4]) -- fromList [1] -difference :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a +difference :: Hashable a => HashSet a -> HashSet a -> HashSet a difference (HashSet a) (HashSet b) = HashSet (H.difference a b) {-# INLINABLE difference #-} @@ -455,12 +455,12 @@ toList t = Exts.build (\ c z -> foldrWithKey (const . c) z (asMap t)) {-# INLINE toList #-} -- | \(O(n \min(W, n))\) Construct a set from a list of elements. -fromList :: (Eq a, Hashable a) => [a] -> HashSet a +fromList :: Hashable a => [a] -> HashSet a fromList = HashSet . List.foldl' (\ m k -> H.unsafeInsert k () m) H.empty {-# INLINE fromList #-} #if defined(__GLASGOW_HASKELL__) -instance (Eq a, Hashable a) => Exts.IsList (HashSet a) where +instance Hashable a => Exts.IsList (HashSet a) where type Item (HashSet a) = a fromList = fromList toList = toList diff --git a/benchmarks/Benchmarks.hs b/benchmarks/Benchmarks.hs index 67591a9b..ce507633 100644 --- a/benchmarks/Benchmarks.hs +++ b/benchmarks/Benchmarks.hs @@ -382,14 +382,14 @@ main = do ------------------------------------------------------------------------ -- * HashMap -lookup :: (Eq k, Hashable k) => [k] -> HM.HashMap k Int -> Int +lookup :: Hashable k => [k] -> HM.HashMap k Int -> Int lookup xs m = foldl' (\z k -> fromMaybe z (HM.lookup k m)) 0 xs {-# SPECIALIZE lookup :: [Int] -> HM.HashMap Int Int -> Int #-} {-# SPECIALIZE lookup :: [String] -> HM.HashMap String Int -> Int #-} {-# SPECIALIZE lookup :: [BS.ByteString] -> HM.HashMap BS.ByteString Int -> Int #-} -insert :: (Eq k, Hashable k) => [(k, Int)] -> HM.HashMap k Int +insert :: Hashable k => [(k, Int)] -> HM.HashMap k Int -> HM.HashMap k Int insert xs m0 = foldl' (\m (k, v) -> HM.insert k v m) m0 xs {-# SPECIALIZE insert :: [(Int, Int)] -> HM.HashMap Int Int @@ -399,7 +399,7 @@ insert xs m0 = foldl' (\m (k, v) -> HM.insert k v m) m0 xs {-# SPECIALIZE insert :: [(BS.ByteString, Int)] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -delete :: (Eq k, Hashable k) => [k] -> HM.HashMap k Int -> HM.HashMap k Int +delete :: Hashable k => [k] -> HM.HashMap k Int -> HM.HashMap k Int delete xs m0 = foldl' (\m k -> HM.delete k m) m0 xs {-# SPECIALIZE delete :: [Int] -> HM.HashMap Int Int -> HM.HashMap Int Int #-} {-# SPECIALIZE delete :: [String] -> HM.HashMap String Int @@ -407,7 +407,7 @@ delete xs m0 = foldl' (\m k -> HM.delete k m) m0 xs {-# SPECIALIZE delete :: [BS.ByteString] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -alterInsert :: (Eq k, Hashable k) => [(k, Int)] -> HM.HashMap k Int +alterInsert :: Hashable k => [(k, Int)] -> HM.HashMap k Int -> HM.HashMap k Int alterInsert xs m0 = foldl' (\m (k, v) -> HM.alter (const . Just $ v) k m) m0 xs @@ -418,7 +418,7 @@ alterInsert xs m0 = {-# SPECIALIZE alterInsert :: [(BS.ByteString, Int)] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -alterDelete :: (Eq k, Hashable k) => [k] -> HM.HashMap k Int +alterDelete :: Hashable k => [k] -> HM.HashMap k Int -> HM.HashMap k Int alterDelete xs m0 = foldl' (\m k -> HM.alter (const Nothing) k m) m0 xs @@ -429,7 +429,7 @@ alterDelete xs m0 = {-# SPECIALIZE alterDelete :: [BS.ByteString] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -alterFInsert :: (Eq k, Hashable k) => [(k, Int)] -> HM.HashMap k Int +alterFInsert :: Hashable k => [(k, Int)] -> HM.HashMap k Int -> HM.HashMap k Int alterFInsert xs m0 = foldl' (\m (k, v) -> runIdentity $ HM.alterF (const . Identity . Just $ v) k m) m0 xs @@ -440,7 +440,7 @@ alterFInsert xs m0 = {-# SPECIALIZE alterFInsert :: [(BS.ByteString, Int)] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -alterFDelete :: (Eq k, Hashable k) => [k] -> HM.HashMap k Int +alterFDelete :: Hashable k => [k] -> HM.HashMap k Int -> HM.HashMap k Int alterFDelete xs m0 = foldl' (\m k -> runIdentity $ HM.alterF (const . Identity $ Nothing) k m) m0 xs @@ -451,7 +451,7 @@ alterFDelete xs m0 = {-# SPECIALIZE alterFDelete :: [BS.ByteString] -> HM.HashMap BS.ByteString Int -> HM.HashMap BS.ByteString Int #-} -isSubmapOfNaive :: (Eq k, Hashable k) => HM.HashMap k Int -> HM.HashMap k Int -> Bool +isSubmapOfNaive :: Hashable k => HM.HashMap k Int -> HM.HashMap k Int -> Bool isSubmapOfNaive m1 m2 = and [ Just v1 == HM.lookup k1 m2 | (k1,v1) <- HM.toList m1 ] {-# SPECIALIZE isSubmapOfNaive :: HM.HashMap Int Int -> HM.HashMap Int Int -> Bool #-} {-# SPECIALIZE isSubmapOfNaive :: HM.HashMap String Int -> HM.HashMap String Int -> Bool #-} @@ -484,13 +484,13 @@ deleteM xs m0 = foldl' (\m k -> M.delete k m) m0 xs ------------------------------------------------------------------------ -- * Map from the hashmap package -lookupIHM :: (Eq k, Hashable k, Ord k) => [k] -> IHM.Map k Int -> Int +lookupIHM :: (Hashable k, Ord k) => [k] -> IHM.Map k Int -> Int lookupIHM xs m = foldl' (\z k -> fromMaybe z (IHM.lookup k m)) 0 xs {-# SPECIALIZE lookupIHM :: [String] -> IHM.Map String Int -> Int #-} {-# SPECIALIZE lookupIHM :: [BS.ByteString] -> IHM.Map BS.ByteString Int -> Int #-} -insertIHM :: (Eq k, Hashable k, Ord k) => [(k, Int)] -> IHM.Map k Int +insertIHM :: (Hashable k, Ord k) => [(k, Int)] -> IHM.Map k Int -> IHM.Map k Int insertIHM xs m0 = foldl' (\m (k, v) -> IHM.insert k v m) m0 xs {-# SPECIALIZE insertIHM :: [(String, Int)] -> IHM.Map String Int @@ -498,7 +498,7 @@ insertIHM xs m0 = foldl' (\m (k, v) -> IHM.insert k v m) m0 xs {-# SPECIALIZE insertIHM :: [(BS.ByteString, Int)] -> IHM.Map BS.ByteString Int -> IHM.Map BS.ByteString Int #-} -deleteIHM :: (Eq k, Hashable k, Ord k) => [k] -> IHM.Map k Int -> IHM.Map k Int +deleteIHM :: (Hashable k, Ord k) => [k] -> IHM.Map k Int -> IHM.Map k Int deleteIHM xs m0 = foldl' (\m k -> IHM.delete k m) m0 xs {-# SPECIALIZE deleteIHM :: [String] -> IHM.Map String Int -> IHM.Map String Int #-} diff --git a/tests/Properties/HashMapLazy.hs b/tests/Properties/HashMapLazy.hs index 7f7f66e8..40c7fd97 100644 --- a/tests/Properties/HashMapLazy.hs +++ b/tests/Properties/HashMapLazy.hs @@ -47,7 +47,7 @@ import qualified Data.HashMap.Lazy as HM import qualified Data.Map.Lazy as M #endif -instance (Eq k, Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where +instance (Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where arbitrary = HM.fromList <$> arbitrary shrink = fmap HM.fromList . shrink . HM.toList @@ -63,7 +63,7 @@ sortByKey = List.sortBy (compare `on` fst) toOrdMap :: Ord k => HashMap k v -> M.Map k v toOrdMap = M.fromList . HM.toList -isValid :: (Eq k, Hashable k, Show k) => HashMap k v -> Property +isValid :: (Hashable k, Show k) => HashMap k v -> Property isValid m = valid m === Valid -- The free magma is used to test that operations are applied in the diff --git a/tests/Properties/HashSet.hs b/tests/Properties/HashSet.hs index 54087e31..1cf0d04c 100644 --- a/tests/Properties/HashSet.hs +++ b/tests/Properties/HashSet.hs @@ -27,11 +27,11 @@ import qualified Data.List as List import qualified Data.Set as S import qualified Test.QuickCheck as QC -instance (Eq k, Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where +instance (Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where arbitrary = HM.fromList <$> arbitrary shrink = fmap HM.fromList . shrink . HM.toList -instance (Eq a, Hashable a, Arbitrary a) => Arbitrary (HashSet a) where +instance (Hashable a, Arbitrary a) => Arbitrary (HashSet a) where arbitrary = HS.fromMap <$> arbitrary shrink = fmap HS.fromMap . shrink . HS.toMap diff --git a/tests/Strictness.hs b/tests/Strictness.hs index b446ce14..64be4c46 100644 --- a/tests/Strictness.hs +++ b/tests/Strictness.hs @@ -21,7 +21,7 @@ import Prelude hiding (Foldable (..)) import qualified Data.HashMap.Strict as HM -instance (Eq k, Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where +instance (Hashable k, Arbitrary k, Arbitrary v) => Arbitrary (HashMap k v) where arbitrary = HM.fromList <$> arbitrary shrink = fmap HM.fromList . shrink . HM.toList