Skip to content

Commit 97af0e8

Browse files
authored
Improve mapping over keys for IntMap and IntSet (#1148)
* Implement the functions in terms of the builders instead of converting to and from a list. This reduces time and allocations. * Document that mapping takes linear time for monotonic functions.
1 parent 17d354f commit 97af0e8

File tree

5 files changed

+57
-26
lines changed

5 files changed

+57
-26
lines changed

containers-tests/benchmarks/IntMap.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ import qualified Data.IntMap.Strict as MS
1010
import qualified Data.IntSet as S
1111
import Data.Maybe (fromMaybe)
1212
import Data.Word (Word8)
13-
import System.Random (StdGen, mkStdGen, randoms)
13+
import System.Random (StdGen, mkStdGen, random, randoms)
1414
import Prelude hiding (lookup)
1515

1616
import Utils.Fold (foldBenchmarks, foldWithKeyBenchmarks)
@@ -55,6 +55,10 @@ main = do
5555
, bench "mapMaybe" $ whnf (M.mapMaybe maybeDel) m
5656
, bench "mapMaybeWithKey" $ whnf (M.mapMaybeWithKey (const maybeDel)) m
5757
, bench "fromList:asc" $ whnf M.fromList elems_asc
58+
, bench "mapKeys:asc" $ whnf (M.mapKeys (+1)) m
59+
, bench "mapKeys:random" $ whnf (M.mapKeys (fst . random . mkStdGen)) m
60+
, bench "mapKeysWith:asc:dups" $ whnf (M.mapKeysWith (+) (`div` 2)) m
61+
, bench "mapKeysMonotonic" $ whnf (M.mapKeysMonotonic (+1)) m
5862
, bench "fromList:asc:fusion" $
5963
whnf (\n -> M.fromList (unitValues [1..n])) bound
6064
, bench "fromList:random" $ whnf M.fromList elems_random

containers-tests/benchmarks/IntSet.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import qualified Data.Set as S
1515
import qualified Data.IntMap as IM
1616
import qualified Data.Map.Strict as M
1717
import Data.Word (Word8)
18-
import System.Random (StdGen, mkStdGen, randoms, randomRs)
18+
import System.Random (StdGen, mkStdGen, randoms, random, randomRs)
1919

2020
import Utils.Fold (foldBenchmarks)
2121

@@ -36,7 +36,9 @@ main = do
3636
defaultMain
3737
[ bench "member" $ whnf (member elems) s
3838
, bench "insert" $ whnf (ins elems) IS.empty
39-
, bench "map" $ whnf (IS.map (+ 1)) s
39+
, bench "map:asc" $ whnf (IS.map (+ 1)) s
40+
, bench "map:random" $ whnf (IS.map (fst . random . mkStdGen)) s
41+
, bench "mapMonotonic" $ whnf (IS.mapMonotonic (+1)) s
4042
, bench "filter" $ whnf (IS.filter ((== 0) . (`mod` 2))) s
4143
, bench "partition" $ whnf (IS.partition ((== 0) . (`mod` 2))) s
4244
, bench "delete" $ whnf (del elems) s

containers/src/Data/IntMap/Internal.hs

Lines changed: 24 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2653,6 +2653,9 @@ mapAccumRWithKey f a t
26532653
-- | \(O(n \min(n,W))\).
26542654
-- @'mapKeys' f s@ is the map obtained by applying @f@ to each key of @s@.
26552655
--
2656+
-- If `f` is monotonically non-decreasing or monotonically non-increasing, this
2657+
-- function takes \(O(n)\) time.
2658+
--
26562659
-- The size of the result may be smaller if @f@ maps two or more distinct
26572660
-- keys to the same new key. In this case the value at the greatest of the
26582661
-- original keys is retained.
@@ -2662,11 +2665,14 @@ mapAccumRWithKey f a t
26622665
-- > mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
26632666

26642667
mapKeys :: (Key->Key) -> IntMap a -> IntMap a
2665-
mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
2668+
mapKeys f t = finishB (foldlWithKey' (\b kx x -> insertB (f kx) x b) emptyB t)
26662669

26672670
-- | \(O(n \min(n,W))\).
26682671
-- @'mapKeysWith' c f s@ is the map obtained by applying @f@ to each key of @s@.
26692672
--
2673+
-- If `f` is monotonically non-decreasing or monotonically non-increasing, this
2674+
-- function takes \(O(n)\) time.
2675+
--
26702676
-- The size of the result may be smaller if @f@ maps two or more distinct
26712677
-- keys to the same new key. In this case the associated values will be
26722678
-- combined using @c@.
@@ -2677,8 +2683,8 @@ mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
26772683
-- Also see the performance note on 'fromListWith'.
26782684

26792685
mapKeysWith :: (a -> a -> a) -> (Key->Key) -> IntMap a -> IntMap a
2680-
mapKeysWith c f
2681-
= fromListWith c . foldrWithKey (\k x xs -> (f k, x) : xs) []
2686+
mapKeysWith c f t =
2687+
finishB (foldlWithKey' (\b kx x -> insertWithB c (f kx) x b) emptyB t)
26822688

26832689
-- | \(O(n)\).
26842690
-- @'mapKeysMonotonic' f s == 'mapKeys' f s@, but works only when @f@
@@ -2700,8 +2706,8 @@ mapKeysWith c f
27002706
-- > mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
27012707

27022708
mapKeysMonotonic :: (Key->Key) -> IntMap a -> IntMap a
2703-
mapKeysMonotonic f
2704-
= fromDistinctAscList . foldrWithKey (\k x xs -> (f k, x) : xs) []
2709+
mapKeysMonotonic f t =
2710+
ascLinkAll (foldlWithKey' (\s kx x -> ascInsert s (f kx) x) MSNada t)
27052711

27062712
{--------------------------------------------------------------------
27072713
Filter
@@ -3487,7 +3493,8 @@ fromListWithKey f xs =
34873493
-- > fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
34883494

34893495
fromAscList :: [(Key,a)] -> IntMap a
3490-
fromAscList xs = fromAscListWithKey (\_ x _ -> x) xs
3496+
fromAscList xs =
3497+
ascLinkAll (Foldable.foldl' (\s (ky, y) -> ascInsert s ky y) MSNada xs)
34913498
{-# INLINE fromAscList #-} -- Inline for list fusion
34923499

34933500
-- | \(O(n)\). Build a map from a list of key\/value pairs where
@@ -3555,6 +3562,17 @@ data MonoState a
35553562
= MSNada
35563563
| MSPush {-# UNPACK #-} !Key a !(Stack a)
35573564

3565+
-- Insert an entry. The key must be >= the last inserted key. If it is equal
3566+
-- to the previous key, the previous value is replaced.
3567+
ascInsert :: MonoState a -> Int -> a -> MonoState a
3568+
ascInsert s !ky y = case s of
3569+
MSNada -> MSPush ky y Nada
3570+
MSPush kx x stk
3571+
| kx == ky -> MSPush ky y stk
3572+
| otherwise -> let m = branchMask kx ky
3573+
in MSPush ky y (ascLinkTop stk kx (Tip kx x) m)
3574+
{-# INLINE ascInsert #-}
3575+
35583576
ascLinkTop :: Stack a -> Int -> IntMap a -> Int -> Stack a
35593577
ascLinkTop stk !rk r !rm = case stk of
35603578
Nada -> Push rm r stk

containers/src/Data/IntMap/Strict/Internal.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -970,6 +970,9 @@ mapAccumRWithKey f0 a0 t0 = toPair $ go f0 a0 t0
970970
-- | \(O(n \min(n,W))\).
971971
-- @'mapKeysWith' c f s@ is the map obtained by applying @f@ to each key of @s@.
972972
--
973+
-- If `f` is monotonically non-decreasing or monotonically non-increasing, this
974+
-- function takes \(O(n)\) time.
975+
--
973976
-- The size of the result may be smaller if @f@ maps two or more distinct
974977
-- keys to the same new key. In this case the associated values will be
975978
-- combined using @c@.
@@ -980,7 +983,8 @@ mapAccumRWithKey f0 a0 t0 = toPair $ go f0 a0 t0
980983
-- Also see the performance note on 'fromListWith'.
981984

982985
mapKeysWith :: (a -> a -> a) -> (Key->Key) -> IntMap a -> IntMap a
983-
mapKeysWith c f = fromListWith c . foldrWithKey (\k x xs -> (f k, x) : xs) []
986+
mapKeysWith c f t =
987+
finishB (foldlWithKey' (\b kx x -> insertWithB c (f kx) x b) emptyB t)
984988

985989
{--------------------------------------------------------------------
986990
Filter

containers/src/Data/IntSet/Internal.hs

Lines changed: 19 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1183,11 +1183,14 @@ deleteMax = maybe Nil snd . maxView
11831183
-- | \(O(n \min(n,W))\).
11841184
-- @'map' f s@ is the set obtained by applying @f@ to each element of @s@.
11851185
--
1186+
-- If `f` is monotonically non-decreasing or monotonically non-increasing, this
1187+
-- function takes \(O(n)\) time.
1188+
--
11861189
-- It's worth noting that the size of the result may be smaller if,
11871190
-- for some @(x,y)@, @x \/= y && f x == f y@
11881191

11891192
map :: (Key -> Key) -> IntSet -> IntSet
1190-
map f = fromList . List.map f . toList
1193+
map f t = finishB (foldl' (\b x -> insertB (f x) b) emptyB t)
11911194

11921195
-- | \(O(n)\). The
11931196
--
@@ -1203,11 +1206,8 @@ map f = fromList . List.map f . toList
12031206
-- precondition may not hold.
12041207
--
12051208
-- @since 0.6.3.1
1206-
1207-
-- Note that for now the test is insufficient to support any fancier implementation.
12081209
mapMonotonic :: (Key -> Key) -> IntSet -> IntSet
1209-
mapMonotonic f = fromDistinctAscList . List.map f . toAscList
1210-
1210+
mapMonotonic f t = ascLinkAll (foldl' (\s x -> ascInsert s (f x)) MSNada t)
12111211

12121212
{--------------------------------------------------------------------
12131213
Fold
@@ -1464,17 +1464,7 @@ fromRange (lx,rx)
14641464

14651465
-- See Note [fromAscList implementation] in Data.IntMap.Internal.
14661466
fromAscList :: [Key] -> IntSet
1467-
fromAscList xs = ascLinkAll (Foldable.foldl' next MSNada xs)
1468-
where
1469-
next s !ky = case s of
1470-
MSNada -> MSPush py bmy Nada
1471-
MSPush px bmx stk
1472-
| px == py -> MSPush py (bmx .|. bmy) stk
1473-
| otherwise -> let m = branchMask px py
1474-
in MSPush py bmy (ascLinkTop stk px (Tip px bmx) m)
1475-
where
1476-
py = prefixOf ky
1477-
bmy = bitmapOf ky
1467+
fromAscList xs = ascLinkAll (Foldable.foldl' ascInsert MSNada xs)
14781468
{-# INLINE fromAscList #-} -- Inline for list fusion
14791469

14801470
-- | \(O(n)\). Build a set from an ascending list of distinct elements.
@@ -1498,6 +1488,19 @@ data MonoState
14981488
= MSNada
14991489
| MSPush {-# UNPACK #-} !Int {-# UNPACK #-} !BitMap !Stack
15001490

1491+
-- Insert an element. The element must be >= the last inserted element.
1492+
ascInsert :: MonoState -> Int -> MonoState
1493+
ascInsert s !ky = case s of
1494+
MSNada -> MSPush py bmy Nada
1495+
MSPush px bmx stk
1496+
| px == py -> MSPush py (bmx .|. bmy) stk
1497+
| otherwise -> let m = branchMask px py
1498+
in MSPush py bmy (ascLinkTop stk px (Tip px bmx) m)
1499+
where
1500+
py = prefixOf ky
1501+
bmy = bitmapOf ky
1502+
{-# INLINE ascInsert #-}
1503+
15011504
ascLinkTop :: Stack -> Int -> IntSet -> Int -> Stack
15021505
ascLinkTop stk !rk r !rm = case stk of
15031506
Nada -> Push rm r stk

0 commit comments

Comments
 (0)