diff --git a/.github/workflows/haskell-ci.yml b/.github/workflows/haskell-ci.yml index 350168c3..1bc148d6 100644 --- a/.github/workflows/haskell-ci.yml +++ b/.github/workflows/haskell-ci.yml @@ -8,9 +8,9 @@ # # For more information, see https://github.com/haskell-CI/haskell-ci # -# version: 0.13.20211116 +# version: 0.14.1 # -# REGENDATA ("0.13.20211116",["github","unordered-containers.cabal"]) +# REGENDATA ("0.14.1",["github","unordered-containers.cabal"]) # name: Haskell-CI on: @@ -37,10 +37,10 @@ jobs: compilerVersion: 9.2.1 setup-method: ghcup allow-failure: false - - compiler: ghc-9.0.1 + - compiler: ghc-9.0.2 compilerKind: ghc - compilerVersion: 9.0.1 - setup-method: hvr-ppa + compilerVersion: 9.0.2 + setup-method: ghcup allow-failure: false - compiler: ghc-8.10.7 compilerKind: ghc @@ -67,11 +67,6 @@ jobs: compilerVersion: 8.2.2 setup-method: hvr-ppa allow-failure: false - - compiler: ghc-8.0.2 - compilerKind: ghc - compilerVersion: 8.0.2 - setup-method: hvr-ppa - allow-failure: false fail-fast: false steps: - name: apt @@ -198,8 +193,8 @@ jobs: touch cabal.project touch cabal.project.local echo "packages: ${PKGDIR_unordered_containers}" >> cabal.project - if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo "package unordered-containers" >> cabal.project ; fi - if [ $((HCNUMVER >= 80200)) -ne 0 ] ; then echo " ghc-options: -Werror=missing-methods" >> cabal.project ; fi + echo "package unordered-containers" >> cabal.project + echo " ghc-options: -Werror=missing-methods" >> cabal.project cat >> cabal.project <> cabal.project.local diff --git a/Data/HashMap/Internal.hs b/Data/HashMap/Internal.hs index cf60bb43..157718b2 100644 --- a/Data/HashMap/Internal.hs +++ b/Data/HashMap/Internal.hs @@ -10,10 +10,8 @@ {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnboxedTuples #-} -#if __GLASGOW_HASKELL__ >= 802 {-# LANGUAGE TypeInType #-} {-# LANGUAGE UnboxedSums #-} -#endif {-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-} {-# OPTIONS_HADDOCK not-home #-} @@ -148,9 +146,7 @@ import Control.Monad.ST (ST, runST) import Data.Bits ((.&.), (.|.), complement, popCount, unsafeShiftL, unsafeShiftR) import Data.Data import qualified Data.Foldable as Foldable -#if MIN_VERSION_base(4,10,0) import Data.Bifoldable -#endif import qualified Data.List as L import GHC.Exts ((==#), build, reallyUnsafePtrEquality#, inline) import Prelude hiding (filter, foldl, foldr, lookup, map, null, pred) @@ -167,17 +163,11 @@ import qualified GHC.Exts as Exts import Data.Functor.Classes import GHC.Stack -#if MIN_VERSION_hashable(1,2,5) import qualified Data.Hashable.Lifted as H -#endif -#if MIN_VERSION_deepseq(1,4,3) import qualified Control.DeepSeq as NF -#endif -#if __GLASGOW_HASKELL__ >= 802 import GHC.Exts (TYPE, Int (..), Int#) -#endif import Data.Functor.Identity (Identity (..)) import Control.Applicative (Const (..)) @@ -205,7 +195,6 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where lift (L k v) = [| L k $! v |] #endif -#if MIN_VERSION_deepseq(1,4,3) -- | @since 0.2.14.0 instance NFData k => NF.NFData1 (Leaf k) where liftRnf rnf2 = NF.liftRnf2 rnf rnf2 @@ -213,7 +202,6 @@ instance NFData k => NF.NFData1 (Leaf k) where -- | @since 0.2.14.0 instance NF.NFData2 Leaf where liftRnf2 rnf1 rnf2 (L k v) = rnf1 k `seq` rnf2 v -#endif -- Invariant: The length of the 1st argument to 'Full' is -- 2^bitsPerSubkey @@ -239,7 +227,6 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where rnf (Full ary) = rnf ary rnf (Collision _ ary) = rnf ary -#if MIN_VERSION_deepseq(1,4,3) -- | @since 0.2.14.0 instance NFData k => NF.NFData1 (HashMap k) where liftRnf rnf2 = NF.liftRnf2 rnf rnf2 @@ -251,7 +238,6 @@ instance NF.NFData2 HashMap where liftRnf2 rnf1 rnf2 (Leaf _ l) = NF.liftRnf2 rnf1 rnf2 l liftRnf2 rnf1 rnf2 (Full ary) = NF.liftRnf (NF.liftRnf2 rnf1 rnf2) ary liftRnf2 rnf1 rnf2 (Collision _ ary) = NF.liftRnf (NF.liftRnf2 rnf1 rnf2) ary -#endif instance Functor (HashMap k) where fmap = map @@ -272,7 +258,6 @@ instance Foldable.Foldable (HashMap k) where length = size {-# INLINE length #-} -#if MIN_VERSION_base(4,10,0) -- | @since 0.2.11 instance Bifoldable HashMap where bifoldMap f g = foldMapWithKey (\ k v -> f k `mappend` g v) @@ -281,7 +266,6 @@ instance Bifoldable HashMap where {-# INLINE bifoldr #-} bifoldl f g = foldlWithKey (\ acc k v -> (acc `f` k) `g` v) {-# INLINE bifoldl #-} -#endif -- | '<>' = 'union' -- @@ -364,7 +348,6 @@ instance (Show k, Show v) => Show (HashMap k v) where instance Traversable (HashMap k) where traverse f = traverseWithKey (const f) - {-# INLINABLE traverse #-} instance Eq2 HashMap where liftEq2 = equal2 @@ -500,7 +483,6 @@ equalKeys = go leafEq (L k1 _) (L k2 _) = k1 == k2 -#if MIN_VERSION_hashable(1,2,5) instance H.Hashable2 HashMap where liftHashWithSalt2 hk hv salt hm = go salt (toList' hm []) where @@ -526,7 +508,6 @@ instance H.Hashable2 HashMap where instance (Hashable k) => H.Hashable1 (HashMap k) where liftHashWithSalt = H.liftHashWithSalt2 H.hashWithSalt -#endif instance (Hashable k, Hashable v) => Hashable (HashMap k v) where hashWithSalt salt hm = go salt hm @@ -601,12 +582,10 @@ member :: (Eq k, Hashable k) => k -> HashMap k a -> Bool member k m = case lookup k m of Nothing -> False Just _ -> True -{-# INLINABLE member #-} -- | /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 -#if __GLASGOW_HASKELL__ >= 802 -- 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. @@ -617,18 +596,10 @@ lookup k m = case lookup# k m of lookup# :: (Eq k, Hashable k) => k -> HashMap k v -> (# (# #) | v #) lookup# k m = lookupCont (\_ -> (# (# #) | #)) (\v _i -> (# | v #)) (hash k) k 0 m -{-# INLINABLE lookup# #-} - -#else - -lookup k m = lookupCont (\_ -> Nothing) (\v _i -> Just v) (hash k) k 0 m -{-# INLINABLE lookup #-} -#endif -- | lookup' is a version of lookup that takes the hash separately. -- It is used to implement alterF. lookup' :: Eq k => Hash -> k -> HashMap k v -> Maybe v -#if __GLASGOW_HASKELL__ >= 802 -- 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. @@ -639,10 +610,6 @@ lookup' h k m = case lookupRecordCollision# h k m of (# (# #) | #) -> Nothing (# | (# a, _i #) #) -> Just a {-# INLINE lookup' #-} -#else -lookup' h k m = lookupCont (\_ -> Nothing) (\v _i -> Just v) h k 0 m -{-# INLINABLE lookup' #-} -#endif -- The result of a lookup, keeping track of if a hash collision occured. -- If a collision did not occur then it will have the Int value (-1). @@ -662,7 +629,6 @@ data LookupRes a = Absent | Present a !Int -- Key in map, no collision => Present v (-1) -- Key in map, collision => Present v position lookupRecordCollision :: Eq k => Hash -> k -> HashMap k v -> LookupRes v -#if __GLASGOW_HASKELL__ >= 802 lookupRecordCollision h k m = case lookupRecordCollision# h k m of (# (# #) | #) -> Absent (# | (# a, i #) #) -> Present a (I# i) -- GHC will eliminate the I# @@ -676,14 +642,6 @@ lookupRecordCollision h k m = case lookupRecordCollision# h k m of lookupRecordCollision# :: Eq k => Hash -> k -> HashMap k v -> (# (# #) | (# v, Int# #) #) lookupRecordCollision# h k m = lookupCont (\_ -> (# (# #) | #)) (\v (I# i) -> (# | (# v, i #) #)) h k 0 m --- INLINABLE to specialize to the Eq instance. -{-# INLINABLE lookupRecordCollision# #-} - -#else /* GHC < 8.2 so there are no unboxed sums */ - -lookupRecordCollision h k m = lookupCont (\_ -> Absent) Present h k 0 m -{-# INLINABLE lookupRecordCollision #-} -#endif -- A two-continuation version of lookupRecordCollision. This lets us -- share source code between lookup and lookupRecordCollision without @@ -698,11 +656,7 @@ lookupRecordCollision h k m = lookupCont (\_ -> Absent) Present h k 0 m -- keys at the top-level of a hashmap, the offset should be 0. When looking up -- keys at level @n@ of a hashmap, the offset should be @n * bitsPerSubkey@. lookupCont :: -#if __GLASGOW_HASKELL__ >= 802 forall rep (r :: TYPE rep) k v. -#else - forall r k v. -#endif Eq k => ((# #) -> r) -- Absent continuation -> (v -> Int -> r) -- Present continuation @@ -750,7 +704,6 @@ findWithDefault :: (Eq k, Hashable k) findWithDefault def k t = case lookup k t of Just v -> v _ -> def -{-# INLINABLE findWithDefault #-} -- | /O(log n)/ Return the value to which the specified key is mapped, @@ -770,7 +723,6 @@ lookupDefault def k t = findWithDefault def k t (!) m k = case lookup k m of Just v -> v Nothing -> error "Data.HashMap.Internal.(!): key not found" -{-# INLINABLE (!) #-} infixl 9 ! @@ -795,7 +747,6 @@ bitmapIndexedOrFull b ary -- the key, the old value is replaced. insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v insert k v m = insert' (hash k) k v m -{-# INLINABLE insert #-} insert' :: Eq k => Hash -> k -> v -> HashMap k v -> HashMap k v insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0 @@ -830,7 +781,6 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0 go h k x s t@(Collision hy v) | h == hy = Collision h (updateOrSnocWith (\a _ -> (# a #)) k x v) | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE insert' #-} -- Insert optimized for the case when we know the key is not in the map. -- @@ -953,7 +903,6 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0) go h k x s t@(Collision hy v) | h == hy = return $! Collision h (updateOrSnocWith (\a _ -> (# a #)) k x v) | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE unsafeInsert #-} -- | Create a map from two key-value pairs which hashes don't collide. To -- enhance sharing, the second key-value pair is represented by the hash of its @@ -1043,7 +992,6 @@ insertModifying x f k0 m0 = go h0 k0 0 m0 then t else Collision h v' | otherwise = go h k s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE insertModifying #-} -- Like insertModifying for arrays; used to implement insertModifying insertModifyingArr :: Eq k => v -> (v -> (# v #)) -> k -> A.Array (Leaf k v) @@ -1070,7 +1018,6 @@ unsafeInsertWith :: forall k v. (Eq k, 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 @@ -1105,13 +1052,11 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) go h k x s t@(Collision hy v) | h == hy = return $! Collision h (updateOrSnocWithKey (\key a b -> (# f key a b #) ) k x v) | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE unsafeInsertWithKey #-} -- | /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 k m = delete' (hash k) k m -{-# INLINABLE delete #-} delete' :: Eq k => Hash -> k -> HashMap k v -> HashMap k v delete' h0 k0 m0 = go h0 k0 0 m0 @@ -1163,7 +1108,6 @@ delete' h0 k0 m0 = go h0 k0 0 m0 | otherwise -> Collision h (A.delete v i) Nothing -> t | otherwise = t -{-# INLINABLE delete' #-} -- | Delete optimized for the case when we know the key is in the map. -- @@ -1262,14 +1206,12 @@ adjust# f k0 m0 = go h0 k0 0 m0 then t else Collision h v' | otherwise = t -{-# INLINABLE adjust# #-} -- | /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 f = alter (>>= f) -{-# INLINABLE update #-} -- | /O(log n)/ The expression @('alter' f k map)@ alters the value @x@ at @k@, or @@ -1286,7 +1228,6 @@ alter f k m = case f (lookup k m) of Nothing -> delete k m Just v -> insert k v m -{-# INLINABLE alter #-} -- | /O(log n)/ The expression @('alterF' f k map)@ alters the value @x@ at -- @k@, or absence thereof. @@ -1433,7 +1374,6 @@ alterFEager f !k m = (<$> f mv) $ \fres -> !mv = case lookupRes of Absent -> Nothing Present v _ -> Just v -{-# INLINABLE alterFEager #-} -- | /O(n*log m)/ Inclusion of maps. A map is included in another map if the keys -- are subsets and the corresponding values are equal: @@ -1452,7 +1392,6 @@ alterFEager f !k m = (<$> f mv) $ \fres -> -- @since 0.2.12 isSubmapOf :: (Eq k, Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool isSubmapOf = (inline isSubmapOfBy) (==) -{-# INLINABLE isSubmapOf #-} -- | /O(n*log m)/ Inclusion of maps with value comparison. A map is included in -- another map if the keys are subsets and if the comparison function is true @@ -1524,7 +1463,6 @@ isSubmapOfBy comp !m1 !m2 = go 0 m1 m2 go _ (BitmapIndexed {}) (Collision {}) = False go _ (Full {}) (Collision {}) = False go _ (Full {}) (BitmapIndexed {}) = False -{-# INLINABLE isSubmapOfBy #-} -- | /O(min n m))/ Checks if a bitmap indexed node is a submap of another. submapBitmapIndexed :: (HashMap k v1 -> HashMap k v2 -> Bool) -> Bitmap -> A.Array (HashMap k v1) -> Bitmap -> A.Array (HashMap k v2) -> Bool @@ -1548,7 +1486,6 @@ submapBitmapIndexed comp !b1 !ary1 !b2 !ary2 = subsetBitmaps && go 0 0 (b1Orb2 . b1Andb2 = b1 .&. b2 b1Orb2 = b1 .|. b2 subsetBitmaps = b1Orb2 == b2 -{-# INLINABLE submapBitmapIndexed #-} ------------------------------------------------------------------------ -- * Combine @@ -1562,7 +1499,6 @@ submapBitmapIndexed comp !b1 !ary1 !b2 !ary2 = subsetBitmaps && go 0 0 (b1Orb2 . -- fromList [(1,'a'),(2,'b'),(3,'d')] union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v union = unionWith const -{-# INLINABLE union #-} -- | /O(n+m)/ The union of two maps. If a key occurs in both maps, -- the provided function (first argument) will be used to compute the @@ -1794,7 +1730,6 @@ difference a b = foldlWithKey' go empty a go m k v = case lookup k b of Nothing -> insert k v m _ -> m -{-# INLINABLE difference #-} -- | /O(n*log m)/ Difference with a combining function. When two equal keys are -- encountered, the combining function is applied to the values of these keys. @@ -1806,7 +1741,6 @@ differenceWith f a b = foldlWithKey' go empty a go m k v = case lookup k b of Nothing -> insert k v m Just w -> maybe m (\y -> insert k y m) (f v w) -{-# INLINABLE differenceWith #-} -- | /O(n*log m)/ Intersection of two maps. Return elements of the first -- map for keys existing in the second. @@ -1816,7 +1750,6 @@ intersection a b = foldlWithKey' go empty a go m k v = case lookup k b of Just _ -> insert k v m _ -> m -{-# INLINABLE intersection #-} -- | /O(n*log m)/ Intersection of two maps. If a key occurs in both maps -- the provided function is used to combine the values from the two @@ -1828,7 +1761,6 @@ intersectionWith f a b = foldlWithKey' go empty a go m k v = case lookup k b of Just w -> insert k (f v w) m _ -> m -{-# INLINABLE intersectionWith #-} -- | /O(n*log m)/ Intersection of two maps. If a key occurs in both maps -- the provided function is used to combine the values from the two @@ -1840,7 +1772,6 @@ intersectionWithKey f a b = foldlWithKey' go empty a go m k v = case lookup k b of Just w -> insert k (f k v w) m _ -> m -{-# INLINABLE intersectionWithKey #-} ------------------------------------------------------------------------ -- * Folds @@ -2083,7 +2014,6 @@ toList t = build (\ c z -> foldrWithKey (curry c) z t) -- contains duplicate mappings, the later mappings take precedence. fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty -{-# INLINABLE fromList #-} -- | /O(n*log n)/ Construct a map from a list of elements. Uses -- the provided function @f@ to merge duplicate entries with @@ -2155,11 +2085,7 @@ fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty -- | /O(n)/ Look up the value associated with the given key in an -- array. lookupInArrayCont :: -#if __GLASGOW_HASKELL__ >= 802 forall rep (r :: TYPE rep) k v. -#else - forall r k v. -#endif Eq k => ((# #) -> r) -> (v -> Int -> r) -> k -> A.Array (Leaf k v) -> r lookupInArrayCont absent present k0 ary0 = go k0 ary0 0 (A.length ary0) where @@ -2183,7 +2109,6 @@ indexOf k0 ary0 = go k0 ary0 0 (A.length ary0) (L kx _) | k == kx -> Just i | otherwise -> go k ary (i+1) n -{-# INLINABLE indexOf #-} updateWith# :: Eq k => (v -> (# v #)) -> k -> A.Array (Leaf k v) -> A.Array (Leaf k v) updateWith# f k0 ary0 = go k0 ary0 0 (A.length ary0) @@ -2196,12 +2121,10 @@ updateWith# f k0 ary0 = go k0 ary0 0 (A.length ary0) | ptrEq y y' -> ary | otherwise -> A.update ary i (L k y') | otherwise -> go k ary (i+1) n -{-# INLINABLE updateWith# #-} updateOrSnocWith :: Eq k => (v -> v -> (# v #)) -> k -> v -> A.Array (Leaf k v) -> A.Array (Leaf k v) updateOrSnocWith f = updateOrSnocWithKey (const f) -{-# INLINABLE updateOrSnocWith #-} updateOrSnocWithKey :: Eq k => (k -> v -> v -> (# v #)) -> k -> v -> A.Array (Leaf k v) -> A.Array (Leaf k v) @@ -2220,11 +2143,9 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0) = A.update ary i (L k v2) | otherwise = go k v ary (i+1) n -{-# INLINABLE updateOrSnocWithKey #-} updateOrConcatWith :: Eq k => (v -> v -> v) -> A.Array (Leaf k v) -> A.Array (Leaf k v) -> A.Array (Leaf k v) updateOrConcatWith f = updateOrConcatWithKey (const f) -{-# INLINABLE updateOrConcatWith #-} updateOrConcatWithKey :: Eq k => (k -> v -> v -> v) -> A.Array (Leaf k v) -> A.Array (Leaf k v) -> A.Array (Leaf k v) updateOrConcatWithKey f ary1 ary2 = A.run $ do @@ -2255,7 +2176,6 @@ updateOrConcatWithKey f ary1 ary2 = A.run $ do go (iEnd+1) (i2+1) go n1 0 return mary -{-# INLINABLE updateOrConcatWithKey #-} -- | /O(n*m)/ Check if the first array is a subset of the second array. subsetArray :: Eq k => (v1 -> v2 -> Bool) -> A.Array (Leaf k v1) -> A.Array (Leaf k v2) -> Bool diff --git a/Data/HashMap/Internal/Array.hs b/Data/HashMap/Internal/Array.hs index aac9cc75..a2215764 100644 --- a/Data/HashMap/Internal/Array.hs +++ b/Data/HashMap/Internal/Array.hs @@ -92,9 +92,7 @@ import qualified Language.Haskell.TH.Syntax as TH import qualified Prelude #endif -#if MIN_VERSION_deepseq(1,4,3) import qualified Control.DeepSeq as NF -#endif import Control.Monad ((>=>)) @@ -173,7 +171,6 @@ rnfArray ary0 = go ary0 n0 0 -- relevant rnf is strict, or in case it actually isn't. {-# INLINE rnfArray #-} -#if MIN_VERSION_deepseq(1,4,3) -- | @since 0.2.14.0 instance NF.NFData1 Array where liftRnf = liftRnfArray @@ -187,7 +184,6 @@ liftRnfArray rnf0 ary0 = go ary0 n0 0 | (# x #) <- index# ary i = rnf0 x `seq` go ary n (i+1) {-# INLINE liftRnfArray #-} -#endif -- | Create a new mutable array of specified size, in the specified -- state thread, with each element containing the specified initial diff --git a/Data/HashMap/Internal/Strict.hs b/Data/HashMap/Internal/Strict.hs index ef74a30f..6fb8dacd 100644 --- a/Data/HashMap/Internal/Strict.hs +++ b/Data/HashMap/Internal/Strict.hs @@ -160,7 +160,6 @@ singleton k !v = HM.singleton k v -- the key, the old value is replaced. insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v insert k !v = HM.insert k v -{-# INLINABLE insert #-} -- | /O(log n)/ Associate the value with the key in this map. If -- this map previously contained a mapping for the key, the old value @@ -200,13 +199,11 @@ insertWith f k0 v0 m0 = go h0 k0 v0 0 m0 go h k x s t@(Collision hy v) | h == hy = Collision h (updateOrSnocWith f k x v) | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE insertWith #-} -- | In-place update version of insertWith unsafeInsertWith :: (Eq k, 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 :: (Eq k, Hashable k) => (k -> v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v @@ -241,7 +238,6 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) go h k x s t@(Collision hy v) | h == hy = return $! Collision h (updateOrSnocWithKey f k x v) | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t) -{-# INLINABLE unsafeInsertWithKey #-} -- | /O(log n)/ Adjust the value tied to a given key in this map only -- if it is present. Otherwise, leave the map alone. @@ -270,14 +266,12 @@ adjust f k0 m0 = go h0 k0 0 m0 go h k _ t@(Collision hy v) | h == hy = Collision h (updateWith f k v) | otherwise = t -{-# INLINABLE adjust #-} -- | /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 f = alter (>>= f) -{-# INLINABLE update #-} -- | /O(log n)/ The expression @('alter' f k map)@ alters the value @x@ at @k@, or -- absence thereof. @@ -292,7 +286,6 @@ alter f k m = case f (HM.lookup k m) of Nothing -> delete k m Just v -> insert k v m -{-# INLINABLE alter #-} -- | /O(log n)/ The expression (@'alterF' f k map@) alters the value @x@ at -- @k@, or absence thereof. @@ -416,7 +409,6 @@ alterFEager f !k !m = (<$> f mv) $ \fres -> !mv = case lookupRes of Absent -> Nothing Present v _ -> Just v -{-# INLINABLE alterFEager #-} ------------------------------------------------------------------------ -- * Combine @@ -594,7 +586,6 @@ differenceWith f a b = foldlWithKey' go empty a go m k v = case HM.lookup k b of Nothing -> insert k v m Just w -> maybe m (\y -> insert k y m) (f v w) -{-# INLINABLE differenceWith #-} -- | /O(n+m)/ Intersection of two maps. If a key occurs in both maps -- the provided function is used to combine the values from the two @@ -606,7 +597,6 @@ intersectionWith f a b = foldlWithKey' go empty a go m k v = case HM.lookup k b of Just w -> insert k (f v w) m _ -> m -{-# INLINABLE intersectionWith #-} -- | /O(n+m)/ Intersection of two maps. If a key occurs in both maps -- the provided function is used to combine the values from the two @@ -618,7 +608,6 @@ intersectionWithKey f a b = foldlWithKey' go empty a go m k v = case HM.lookup k b of Just w -> insert k (f k v w) m _ -> m -{-# INLINABLE intersectionWithKey #-} ------------------------------------------------------------------------ -- ** Lists @@ -628,7 +617,6 @@ intersectionWithKey f a b = foldlWithKey' go empty a -- precedence. fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty -{-# INLINABLE fromList #-} -- | /O(n*log n)/ Construct a map from a list of elements. Uses -- the provided function @f@ to merge duplicate entries with @@ -705,7 +693,6 @@ updateWith f k0 ary0 = go k0 ary0 0 (A.length ary0) | otherwise = case A.index ary i of (L kx y) | k == kx -> let !v' = f y in A.update ary i (L k v') | otherwise -> go k ary (i+1) n -{-# INLINABLE updateWith #-} -- | Append the given key and value to the array. If the key is -- already present, instead update the value of the key by applying @@ -715,7 +702,6 @@ updateWith f k0 ary0 = go k0 ary0 0 (A.length ary0) updateOrSnocWith :: Eq k => (v -> v -> v) -> k -> v -> A.Array (Leaf k v) -> A.Array (Leaf k v) updateOrSnocWith f = updateOrSnocWithKey (const f) -{-# INLINABLE updateOrSnocWith #-} -- | Append the given key and value to the array. If the key is -- already present, instead update the value of the key by applying @@ -737,7 +723,6 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0) | otherwise = case A.index ary i of (L kx y) | k == kx -> let !v' = f k v y in A.update ary i (L k v') | otherwise -> go k v ary (i+1) n -{-# INLINABLE updateOrSnocWithKey #-} ------------------------------------------------------------------------ -- Smart constructors diff --git a/Data/HashSet/Internal.hs b/Data/HashSet/Internal.hs index e0ed5fe3..3800da7d 100644 --- a/Data/HashSet/Internal.hs +++ b/Data/HashSet/Internal.hs @@ -106,13 +106,9 @@ import qualified Data.HashMap.Internal as H import qualified Data.List as List import Text.Read -#if MIN_VERSION_hashable(1,2,5) import qualified Data.Hashable.Lifted as H -#endif -#if MIN_VERSION_deepseq(1,4,3) import qualified Control.DeepSeq as NF -#endif import qualified Language.Haskell.TH.Syntax as TH -- | A set of values. A set cannot contain duplicate values. @@ -129,11 +125,9 @@ instance (NFData a) => NFData (HashSet a) where rnf = rnf . asMap {-# INLINE rnf #-} -#if MIN_VERSION_deepseq(1,4,3) -- | @since 0.2.14.0 instance NF.NFData1 HashSet where liftRnf rnf1 = NF.liftRnf2 rnf1 rnf . asMap -#endif -- | Note that, in the presence of hash collisions, equal @HashSet@s may -- behave differently, i.e. substitutivity may be violated: @@ -245,10 +239,8 @@ instance (Data a, Eq a, Hashable a) => Data (HashSet a) where dataTypeOf _ = hashSetDataType dataCast1 f = gcast1 f -#if MIN_VERSION_hashable(1,2,6) instance H.Hashable1 HashSet where liftHashWithSalt h s = H.liftHashWithSalt2 h hashWithSalt s . asMap -#endif instance (Hashable a) => Hashable (HashSet a) where hashWithSalt salt = hashWithSalt salt . asMap @@ -272,7 +264,6 @@ empty = HashSet H.empty -- fromList [1] singleton :: Hashable a => a -> HashSet a singleton a = HashSet (H.singleton a ()) -{-# INLINABLE singleton #-} -- | /O(1)/ Convert to set to the equivalent 'HashMap' with @()@ values. -- @@ -360,7 +351,6 @@ member :: (Eq a, Hashable a) => a -> HashSet a -> Bool member a s = case H.lookup a (asMap s) of Just _ -> True _ -> False -{-# INLINABLE member #-} -- | /O(log n)/ Add the specified value to this set. -- @@ -368,7 +358,6 @@ member a s = case H.lookup a (asMap s) of -- fromList [1] insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a insert a = HashSet . H.insert a () . asMap -{-# INLINABLE insert #-} -- | /O(log n)/ Remove the specified value from this set if present. -- @@ -378,7 +367,6 @@ insert a = HashSet . H.insert a () . asMap -- fromList [4,5,6] delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a delete a = HashSet . H.delete a . asMap -{-# INLINABLE delete #-} -- | /O(n)/ Transform this set by applying a function to every value. -- The resulting set may be smaller than the source. @@ -396,7 +384,6 @@ map f = fromList . List.map f . toList -- fromList [1] difference :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a difference (HashSet a) (HashSet b) = HashSet (H.difference a b) -{-# INLINABLE difference #-} -- | /O(n)/ Intersection of two sets. Return elements present in both -- the first set and the second. @@ -405,7 +392,6 @@ difference (HashSet a) (HashSet b) = HashSet (H.difference a b) -- fromList [2,3] intersection :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a intersection (HashSet a) (HashSet b) = HashSet (H.intersection a b) -{-# INLINABLE intersection #-} -- | /O(n)/ Reduce this set by applying a binary operator to all -- elements, using the given starting value (typically the diff --git a/docs/developer-guide.md b/docs/developer-guide.md index 07bba306..0917ed59 100644 --- a/docs/developer-guide.md +++ b/docs/developer-guide.md @@ -120,9 +120,9 @@ important functions and the memory layout is about as good as we can get using GHC. Avoiding allocation is done by making things strict (laziness is the enemy of -predictable performance) and using `INLINABLE` to allow to be specialized at the -call site (so key and value arguments to functions are passed as values rather -than pointers to heap objects). +predictable performance) and using `INLINABLE` / `-fexpose-all-unfoldings` to +allow to be specialized at the call site (so key and value arguments to +functions are passed as values rather than pointers to heap objects). The main remaining bottlenecks are due to e.g. GHC not allowing us to unpack an array into a constructor. Two examples: the `Full` constructor is a separate diff --git a/tests/Properties/HashMapLazy.hs b/tests/Properties/HashMapLazy.hs index e1d582bd..b783c4f1 100644 --- a/tests/Properties/HashMapLazy.hs +++ b/tests/Properties/HashMapLazy.hs @@ -12,9 +12,7 @@ module Properties.HashMapLazy (tests) where import Control.Monad ( guard ) import qualified Data.Foldable as Foldable -#if MIN_VERSION_base(4,10,0) import Data.Bifoldable -#endif import Data.Function (on) import Data.Hashable (Hashable(hashWithSalt)) import qualified Data.List as L @@ -337,7 +335,6 @@ pFoldr = (L.sort . M.foldr (:) []) `eq` (L.sort . HM.foldr (:) []) pFoldl :: [(Int, Int)] -> Bool pFoldl = (L.sort . M.foldl (flip (:)) []) `eq` (L.sort . HM.foldl (flip (:)) []) -#if MIN_VERSION_base(4,10,0) pBifoldMap :: [(Int, Int)] -> Bool pBifoldMap xs = concatMap f (HM.toList m) == bifoldMap (:[]) (:[]) m where f (k, v) = [k, v] @@ -352,7 +349,6 @@ pBifoldl :: [(Int, Int)] -> Bool pBifoldl xs = reverse (concatMap f $ HM.toList m) == bifoldl (flip (:)) (flip (:)) [] m where f (k, v) = [k, v] m = HM.fromList xs -#endif pFoldrWithKey :: [(Int, Int)] -> Bool pFoldrWithKey = (sortByKey . M.foldrWithKey f []) `eq` @@ -514,11 +510,9 @@ tests = , testGroup "folds" [ testProperty "foldr" pFoldr , testProperty "foldl" pFoldl -#if MIN_VERSION_base(4,10,0) , testProperty "bifoldMap" pBifoldMap , testProperty "bifoldr" pBifoldr , testProperty "bifoldl" pBifoldl -#endif , testProperty "foldrWithKey" pFoldrWithKey , testProperty "foldlWithKey" pFoldlWithKey , testProperty "foldrWithKey'" pFoldrWithKey' diff --git a/unordered-containers.cabal b/unordered-containers.cabal index 1dc086ac..04083965 100644 --- a/unordered-containers.cabal +++ b/unordered-containers.cabal @@ -30,13 +30,12 @@ extra-source-files: CHANGES.md tested-with: GHC ==9.2.1 - || ==9.0.1 + || ==9.0.2 || ==8.10.7 || ==8.8.4 || ==8.6.5 || ==8.4.4 || ==8.2.2 - || ==8.0.2 flag debug description: Enable debug support @@ -54,9 +53,9 @@ library Data.HashSet.Internal build-depends: - base >= 4.9 && < 5, - deepseq >= 1.1, - hashable >= 1.0.1.1 && < 1.5, + base >= 4.10 && < 5, + deepseq >= 1.4.3, + hashable >= 1.2.5 && < 1.5, template-haskell < 2.19 default-language: Haskell2010 @@ -68,13 +67,8 @@ library MagicHash, BangPatterns - ghc-options: -Wall -O2 -fwarn-tabs -ferror-spans + ghc-options: -Wall -O2 -ferror-spans -fexpose-all-unfoldings - if impl (ghc < 8.2) - -- This is absolutely necessary (but not sufficient) for correctness due to - -- the referential-transparency-breaking mutability in unsafeInsertWith. See - -- #147 and GHC #13615 for details. The bug was fixed in GHC 8.2. - ghc-options: -feager-blackholing if flag(debug) cpp-options: -DASSERTS @@ -95,7 +89,7 @@ test-suite unordered-containers-tests base, ChasingBottoms, containers >= 0.5.8, - hashable >= 1.0.1.1, + hashable, HUnit, QuickCheck >= 2.4.0.1, random, @@ -122,8 +116,8 @@ benchmark benchmarks base >= 4.8.0, bytestring >= 0.10.0.0, containers, - deepseq >= 1.4, - hashable >= 1.0.1.1, + deepseq, + hashable, hashmap, mtl, random, diff --git a/utils/Stats.hs b/utils/Stats.hs index 8b01ecdc..c0150c82 100644 --- a/utils/Stats.hs +++ b/utils/Stats.hs @@ -27,9 +27,6 @@ instance Semigroup Histogram where instance Monoid Histogram where mempty = H 0 0 0 0 0 -#if __GLASGOW_HASKELL__ < 803 - mappend = (<>) -#endif -- | Count the number of node types at each level nodeHistogram :: HM.HashMap k v -> [Histogram]