@@ -107,6 +107,8 @@ module Data.HashMap.Base
107
107
, insertModifying
108
108
, ptrEq
109
109
, adjust #
110
+ , unionWithKey #
111
+ , unsafeInsertModifying
110
112
) where
111
113
112
114
#if __GLASGOW_HASKELL__ < 710
@@ -650,7 +652,7 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0
650
652
else Full (update16 ary i st')
651
653
where i = index h s
652
654
go h k x s t@ (Collision hy v)
653
- | h == hy = Collision h (updateOrSnocWith const k x v)
655
+ | h == hy = Collision h (updateOrSnocWith ( \ v1 _ -> ( # v1 # )) k x v)
654
656
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
655
657
{-# INLINABLE insert' #-}
656
658
@@ -773,7 +775,7 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
773
775
return t
774
776
where i = index h s
775
777
go h k x s t@ (Collision hy v)
776
- | h == hy = return $! Collision h (updateOrSnocWith const k x v)
778
+ | h == hy = return $! Collision h (updateOrSnocWith ( \ v1 _ -> ( # v1 # )) k x v)
777
779
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
778
780
{-# INLINABLE unsafeInsert #-}
779
781
@@ -809,30 +811,30 @@ insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v
809
811
-> HashMap k v
810
812
-- We're not going to worry about allocating a function closure
811
813
-- to pass to insertModifying. See comments at 'adjust'.
812
- insertWith f k new m = insertModifying new (\ old -> (# f new old # )) k m
814
+ insertWith f k new m = insertModifying ( \ _ -> ( # new # )) (\ old -> (# f new old # )) k m
813
815
{-# INLINE insertWith #-}
814
816
815
817
-- | @insertModifying@ is a lot like insertWith; we use it to implement alterF.
816
818
-- It takes a value to insert when the key is absent and a function
817
819
-- to apply to calculate a new value when the key is present. Thanks
818
820
-- to the unboxed unary tuple, we avoid introducing any unnecessary
819
821
-- thunks in the tree.
820
- insertModifying :: (Eq k , Hashable k ) => v -> (v -> (# v # )) -> k -> HashMap k v
822
+ insertModifying :: (Eq k , Hashable k ) => (( # # ) -> ( # v # )) -> (v -> (# v # )) -> k -> HashMap k v
821
823
-> HashMap k v
822
824
insertModifying x f k0 m0 = go h0 k0 0 m0
823
825
where
824
826
! h0 = hash k0
825
- go ! h ! k ! _ Empty = Leaf h (L k x )
827
+ go ! h ! k ! _ Empty = case x ( # # ) of ( # new # ) -> Leaf h (L k new )
826
828
go h k s t@ (Leaf hy l@ (L ky y))
827
829
| hy == h = if ky == k
828
830
then case f y of
829
831
(# v' # ) | ptrEq y v' -> t
830
832
| otherwise -> Leaf h (L k (v'))
831
- else collision h l (L k x )
832
- | otherwise = runST (two s h k x hy ky y)
833
+ else case x ( # # ) of ( # new # ) -> collision h l (L k new )
834
+ | otherwise = case x ( # # ) of ( # new # ) -> runST (two s h k new hy ky y)
833
835
go h k s t@ (BitmapIndexed b ary)
834
836
| b .&. m == 0 =
835
- let ary' = A. insert ary i $! Leaf h (L k x )
837
+ let ary' = case x ( # # ) of ( # new # ) -> A. insert ary i $! Leaf h (L k new )
836
838
in bitmapIndexedOrFull (b .|. m) ary'
837
839
| otherwise =
838
840
let ! st = A. index ary i
@@ -861,7 +863,7 @@ insertModifying x f k0 m0 = go h0 k0 0 m0
861
863
{-# INLINABLE insertModifying #-}
862
864
863
865
-- Like insertModifying for arrays; used to implement insertModifying
864
- insertModifyingArr :: Eq k => v -> (v -> (# v # )) -> k -> A. Array (Leaf k v )
866
+ insertModifyingArr :: Eq k => (( # # ) -> ( # v # )) -> (v -> (# v # )) -> k -> A. Array (Leaf k v )
865
867
-> A. Array (Leaf k v )
866
868
insertModifyingArr x f k0 ary0 = go k0 ary0 0 (A. length ary0)
867
869
where
@@ -870,7 +872,7 @@ insertModifyingArr x f k0 ary0 = go k0 ary0 0 (A.length ary0)
870
872
-- Not found, append to the end.
871
873
mary <- A. new_ (n + 1 )
872
874
A. copy ary 0 mary 0 n
873
- A. write mary n (L k x )
875
+ case x ( # # ) of ( # new # ) -> A. write mary n (L k new )
874
876
return mary
875
877
| otherwise = case A. index ary i of
876
878
(L kx y) | k == kx -> case f y of
@@ -881,40 +883,40 @@ insertModifyingArr x f k0 ary0 = go k0 ary0 0 (A.length ary0)
881
883
{-# INLINE insertModifyingArr #-}
882
884
883
885
-- | In-place update version of insertWith
884
- unsafeInsertWith :: forall k v . (Eq k , Hashable k )
885
- => (v -> v -> v ) -> k -> v -> HashMap k v
886
+ unsafeInsertModifying :: forall k v . (Eq k , Hashable k )
887
+ => (( # # ) -> ( # v # )) -> ( v -> ( # v # )) -> k -> HashMap k v
886
888
-> HashMap k v
887
- unsafeInsertWith f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
889
+ unsafeInsertModifying v0 f k0 m0 = runST (go h0 k0 0 m0)
888
890
where
889
891
h0 = hash k0
890
- go :: Hash -> k -> v -> Shift -> HashMap k v -> ST s (HashMap k v )
891
- go ! h ! k x ! _ Empty = return $! Leaf h (L k x)
892
- go h k x s (Leaf hy l@ (L ky y))
892
+ go :: Hash -> k -> Shift -> HashMap k v -> ST s (HashMap k v )
893
+ go ! h ! k ! _ Empty = case v0 ( # # ) of ( # x # ) -> return $! Leaf h (L k x)
894
+ go h k s (Leaf hy l@ (L ky y))
893
895
| hy == h = if ky == k
894
- then return $! Leaf h (L k (f x y) )
895
- else return $! collision h l (L k x)
896
- | otherwise = two s h k x hy ky y
897
- go h k x s t@ (BitmapIndexed b ary)
896
+ then case f y of ( # v # ) -> return $! Leaf h (L k v )
897
+ else case v0 ( # # ) of ( # x # ) -> return $! collision h l (L k x)
898
+ | otherwise = case v0 ( # # ) of ( # x # ) -> two s h k x hy ky y
899
+ go h k s t@ (BitmapIndexed b ary)
898
900
| b .&. m == 0 = do
899
- ary' <- A. insertM ary i $! Leaf h (L k x)
901
+ ary' <- case v0 ( # # ) of ( # x # ) -> A. insertM ary i $! Leaf h (L k x)
900
902
return $! bitmapIndexedOrFull (b .|. m) ary'
901
903
| otherwise = do
902
904
st <- A. indexM ary i
903
- st' <- go h k x (s+ bitsPerSubkey) st
905
+ st' <- go h k (s+ bitsPerSubkey) st
904
906
A. unsafeUpdateM ary i st'
905
907
return t
906
908
where m = mask h s
907
909
i = sparseIndex b m
908
- go h k x s t@ (Full ary) = do
910
+ go h k s t@ (Full ary) = do
909
911
st <- A. indexM ary i
910
- st' <- go h k x (s+ bitsPerSubkey) st
912
+ st' <- go h k (s+ bitsPerSubkey) st
911
913
A. unsafeUpdateM ary i st'
912
914
return t
913
915
where i = index h s
914
- go h k x s t@ (Collision hy v)
915
- | h == hy = return $! Collision h (updateOrSnocWith f k x v)
916
- | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
917
- {-# INLINABLE unsafeInsertWith #-}
916
+ go h k s t@ (Collision hy v)
917
+ | h == hy = return $! Collision h (insertModifyingArr v0 f k v)
918
+ | otherwise = go h k s $ BitmapIndexed (mask hy s) (A. singleton t)
919
+ {-# INLINABLE unsafeInsertModifying #-}
918
920
919
921
-- | /O(log n)/ Remove the mapping for the specified key from this map
920
922
-- if present.
@@ -1157,7 +1159,7 @@ bogus# _ = error "Data.HashMap.alterF internal error: hit bogus#"
1157
1159
-- We delay this rule to stage 1 so alterFconstant has a chance to fire.
1158
1160
"alterFinsertWith" [1] forall (f :: Maybe a -> Identity (Maybe a)) x y.
1159
1161
alterFWeird (coerce (Just x)) (coerce (Just y)) f =
1160
- coerce (insertModifying x (\mold -> case runIdentity (f (Just mold)) of
1162
+ coerce (insertModifying (\_ -> (# x #)) (\mold -> case runIdentity (f (Just mold)) of
1161
1163
Nothing -> bogus# (# #)
1162
1164
Just new -> (# new #)))
1163
1165
@@ -1256,22 +1258,27 @@ unionWith f = unionWithKey (const f)
1256
1258
-- result.
1257
1259
unionWithKey :: (Eq k , Hashable k ) => (k -> v -> v -> v ) -> HashMap k v -> HashMap k v
1258
1260
-> HashMap k v
1259
- unionWithKey f = go 0
1261
+ unionWithKey f m = unionWithKey# (\ k v1 v2 -> (# f k v1 v2 # )) m
1262
+ {-# INLINE unionWithKey #-}
1263
+
1264
+ unionWithKey# :: (Eq k , Hashable k ) => (k -> v -> v -> (# v # )) -> HashMap k v -> HashMap k v
1265
+ -> HashMap k v
1266
+ unionWithKey# f = go 0
1260
1267
where
1261
1268
-- empty vs. anything
1262
1269
go ! _ t1 Empty = t1
1263
1270
go _ Empty t2 = t2
1264
1271
-- leaf vs. leaf
1265
1272
go s t1@ (Leaf h1 l1@ (L k1 v1)) t2@ (Leaf h2 l2@ (L k2 v2))
1266
1273
| h1 == h2 = if k1 == k2
1267
- then Leaf h1 ( L k1 ( f k1 v1 v2) )
1274
+ then case f k1 v1 v2 of ( # v # ) -> Leaf h1 ( L k1 v )
1268
1275
else collision h1 l1 l2
1269
1276
| otherwise = goDifferentHash s h1 h2 t1 t2
1270
1277
go s t1@ (Leaf h1 (L k1 v1)) t2@ (Collision h2 ls2)
1271
1278
| h1 == h2 = Collision h1 (updateOrSnocWithKey f k1 v1 ls2)
1272
1279
| otherwise = goDifferentHash s h1 h2 t1 t2
1273
1280
go s t1@ (Collision h1 ls1) t2@ (Leaf h2 (L k2 v2))
1274
- | h1 == h2 = Collision h1 (updateOrSnocWithKey (flip . f ) k2 v2 ls1)
1281
+ | h1 == h2 = Collision h1 (updateOrSnocWithKey (\ q w x -> f q x w ) k2 v2 ls1)
1275
1282
| otherwise = goDifferentHash s h1 h2 t1 t2
1276
1283
go s t1@ (Collision h1 ls1) t2@ (Collision h2 ls2)
1277
1284
| h1 == h2 = Collision h1 (updateOrConcatWithKey f ls1 ls2)
@@ -1336,7 +1343,8 @@ unionWithKey f = go 0
1336
1343
where
1337
1344
m1 = mask h1 s
1338
1345
m2 = mask h2 s
1339
- {-# INLINE unionWithKey #-}
1346
+ {-# INLINE unionWithKey# #-}
1347
+
1340
1348
1341
1349
-- | Strict in the result of @f@.
1342
1350
unionArrayBy :: (a -> a -> a ) -> Bitmap -> Bitmap -> A. Array a -> A. Array a
@@ -1667,7 +1675,7 @@ fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty
1667
1675
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
1668
1676
-- the provided function to merge duplicate entries.
1669
1677
fromListWith :: (Eq k , Hashable k ) => (v -> v -> v ) -> [(k , v )] -> HashMap k v
1670
- fromListWith f = L. foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
1678
+ fromListWith f = L. foldl' (\ m (k, v) -> unsafeInsertModifying ( \ _ -> ( # v # )) ( \ y -> ( # f v y # )) k m) empty
1671
1679
{-# INLINE fromListWith #-}
1672
1680
1673
1681
------------------------------------------------------------------------
@@ -1719,12 +1727,12 @@ updateWith# f k0 ary0 = go k0 ary0 0 (A.length ary0)
1719
1727
| otherwise -> go k ary (i+ 1 ) n
1720
1728
{-# INLINABLE updateWith# #-}
1721
1729
1722
- updateOrSnocWith :: Eq k => (v -> v -> v ) -> k -> v -> A. Array (Leaf k v )
1730
+ updateOrSnocWith :: Eq k => (v -> v -> ( # v # ) ) -> k -> v -> A. Array (Leaf k v )
1723
1731
-> A. Array (Leaf k v )
1724
1732
updateOrSnocWith f = updateOrSnocWithKey (const f)
1725
1733
{-# INLINABLE updateOrSnocWith #-}
1726
1734
1727
- updateOrSnocWithKey :: Eq k => (k -> v -> v -> v ) -> k -> v -> A. Array (Leaf k v )
1735
+ updateOrSnocWithKey :: Eq k => (k -> v -> v -> ( # v # ) ) -> k -> v -> A. Array (Leaf k v )
1728
1736
-> A. Array (Leaf k v )
1729
1737
updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A. length ary0)
1730
1738
where
@@ -1736,15 +1744,15 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
1736
1744
A. write mary n (L k v)
1737
1745
return mary
1738
1746
| otherwise = case A. index ary i of
1739
- (L kx y) | k == kx -> A. update ary i (L k (f k v y) )
1747
+ (L kx y) | k == kx -> case f k v y of ( # y' # ) -> A. update ary i (L k y' )
1740
1748
| otherwise -> go k v ary (i+ 1 ) n
1741
1749
{-# INLINABLE updateOrSnocWithKey #-}
1742
1750
1743
- updateOrConcatWith :: Eq k => (v -> v -> v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
1751
+ updateOrConcatWith :: Eq k => (v -> v -> ( # v # ) ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
1744
1752
updateOrConcatWith f = updateOrConcatWithKey (const f)
1745
1753
{-# INLINABLE updateOrConcatWith #-}
1746
1754
1747
- updateOrConcatWithKey :: Eq k => (k -> v -> v -> v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
1755
+ updateOrConcatWithKey :: Eq k => (k -> v -> v -> ( # v # ) ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
1748
1756
updateOrConcatWithKey f ary1 ary2 = A. run $ do
1749
1757
-- first: look up the position of each element of ary2 in ary1
1750
1758
let indices = A. map (\ (L k _) -> indexOf k ary1) ary2
@@ -1763,7 +1771,7 @@ updateOrConcatWithKey f ary1 ary2 = A.run $ do
1763
1771
Just i1 -> do -- key occurs in both arrays, store combination in position i1
1764
1772
L k v1 <- A. indexM ary1 i1
1765
1773
L _ v2 <- A. indexM ary2 i2
1766
- A. write mary i1 (L k (f k v1 v2) )
1774
+ case f k v1 v2 of ( # v' # ) -> A. write mary i1 (L k v' )
1767
1775
go iEnd (i2+ 1 )
1768
1776
Nothing -> do -- key is only in ary2, append to end
1769
1777
A. write mary iEnd =<< A. indexM ary2 i2
0 commit comments