Skip to content

Commit e9f827d

Browse files
committed
Make Int{Map,Set} folds friendlier to optimizations
1 parent 50a1b4d commit e9f827d

File tree

2 files changed

+157
-44
lines changed

2 files changed

+157
-44
lines changed

containers/src/Data/IntMap/Internal.hs

Lines changed: 117 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -325,7 +325,7 @@ import Data.Bits
325325
import qualified Data.Foldable as Foldable
326326
import Data.Maybe (fromMaybe)
327327
import Utils.Containers.Internal.Prelude hiding
328-
(lookup, map, filter, foldr, foldl, foldl', null)
328+
(lookup, map, filter, foldr, foldl, foldl', foldMap, null)
329329
import Prelude ()
330330

331331
import Data.IntSet.Internal (IntSet)
@@ -469,23 +469,13 @@ instance Semigroup (IntMap a) where
469469

470470
-- | Folds in order of increasing key.
471471
instance Foldable.Foldable IntMap where
472-
fold = go
473-
where go Nil = mempty
474-
go (Tip _ v) = v
475-
go (Bin p l r)
476-
| signBranch p = go r `mappend` go l
477-
| otherwise = go l `mappend` go r
472+
fold = foldMap id
478473
{-# INLINABLE fold #-}
479474
foldr = foldr
480475
{-# INLINE foldr #-}
481476
foldl = foldl
482477
{-# INLINE foldl #-}
483-
foldMap f t = go t
484-
where go Nil = mempty
485-
go (Tip _ v) = f v
486-
go (Bin p l r)
487-
| signBranch p = go r `mappend` go l
488-
| otherwise = go l `mappend` go r
478+
foldMap = foldMap
489479
{-# INLINE foldMap #-}
490480
foldl' = foldl'
491481
{-# INLINE foldl' #-}
@@ -3012,31 +3002,37 @@ splitLookup k t =
30123002
--
30133003
-- > let f a len = len + (length a)
30143004
-- > foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
3005+
3006+
-- See Note [IntMap folds]
30153007
foldr :: (a -> b -> b) -> b -> IntMap a -> b
30163008
foldr f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30173009
case t of
3010+
Nil -> z
30183011
Bin p l r
30193012
| signBranch p -> go (go z l) r -- put negative numbers before
30203013
| otherwise -> go (go z r) l
30213014
_ -> go z t
30223015
where
3023-
go z' Nil = z'
3016+
go _ Nil = error "foldr.go: Nil"
30243017
go z' (Tip _ x) = f x z'
30253018
go z' (Bin _ l r) = go (go z' r) l
30263019
{-# INLINE foldr #-}
30273020

30283021
-- | \(O(n)\). A strict version of 'foldr'. Each application of the operator is
30293022
-- evaluated before using the result in the next application. This
30303023
-- function is strict in the starting value.
3024+
3025+
-- See Note [IntMap folds]
30313026
foldr' :: (a -> b -> b) -> b -> IntMap a -> b
30323027
foldr' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30333028
case t of
3029+
Nil -> z
30343030
Bin p l r
30353031
| signBranch p -> go (go z l) r -- put negative numbers before
30363032
| otherwise -> go (go z r) l
30373033
_ -> go z t
30383034
where
3039-
go !z' Nil = z'
3035+
go !_ Nil = error "foldr'.go: Nil"
30403036
go z' (Tip _ x) = f x z'
30413037
go z' (Bin _ l r) = go (go z' r) l
30423038
{-# INLINE foldr' #-}
@@ -3050,35 +3046,65 @@ foldr' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30503046
--
30513047
-- > let f len a = len + (length a)
30523048
-- > foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
3049+
3050+
-- See Note [IntMap folds]
30533051
foldl :: (a -> b -> a) -> a -> IntMap b -> a
30543052
foldl f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30553053
case t of
3054+
Nil -> z
30563055
Bin p l r
30573056
| signBranch p -> go (go z r) l -- put negative numbers before
30583057
| otherwise -> go (go z l) r
30593058
_ -> go z t
30603059
where
3061-
go z' Nil = z'
3060+
go _ Nil = error "foldl.go: Nil"
30623061
go z' (Tip _ x) = f z' x
30633062
go z' (Bin _ l r) = go (go z' l) r
30643063
{-# INLINE foldl #-}
30653064

30663065
-- | \(O(n)\). A strict version of 'foldl'. Each application of the operator is
30673066
-- evaluated before using the result in the next application. This
30683067
-- function is strict in the starting value.
3068+
3069+
-- See Note [IntMap folds]
30693070
foldl' :: (a -> b -> a) -> a -> IntMap b -> a
30703071
foldl' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30713072
case t of
3073+
Nil -> z
30723074
Bin p l r
30733075
| signBranch p -> go (go z r) l -- put negative numbers before
30743076
| otherwise -> go (go z l) r
30753077
_ -> go z t
30763078
where
3077-
go !z' Nil = z'
3079+
go !_ Nil = error "foldl'.go: Nil"
30783080
go z' (Tip _ x) = f z' x
30793081
go z' (Bin _ l r) = go (go z' l) r
30803082
{-# INLINE foldl' #-}
30813083

3084+
-- See Note [IntMap folds]
3085+
foldMap :: Monoid m => (a -> m) -> IntMap a -> m
3086+
foldMap f = \t -> -- Use lambda to be inlinable with two arguments.
3087+
case t of
3088+
Nil -> mempty
3089+
Bin p l r
3090+
#if MIN_VERSION_base(4,11,0)
3091+
| signBranch p -> go r <> go l
3092+
| otherwise -> go l <> go r
3093+
#else
3094+
| signBranch p -> go r `mappend` go l
3095+
| otherwise -> go l `mappend` go r
3096+
#endif
3097+
_ -> go t
3098+
where
3099+
go Nil = error "foldMap.go: Nil"
3100+
go (Tip _ x) = f x
3101+
#if MIN_VERSION_base(4,11,0)
3102+
go (Bin _ l r) = go l <> go r
3103+
#else
3104+
go (Bin _ l r) = go l `mappend` go r
3105+
#endif
3106+
{-# INLINE foldMap #-}
3107+
30823108
-- | \(O(n)\). Fold the keys and values in the map using the given right-associative
30833109
-- binary operator, such that
30843110
-- @'foldrWithKey' f z == 'Prelude.foldr' ('uncurry' f) z . 'toAscList'@.
@@ -3089,31 +3115,37 @@ foldl' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30893115
--
30903116
-- > let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
30913117
-- > foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
3118+
3119+
-- See Note [IntMap folds]
30923120
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b
30933121
foldrWithKey f z = \t -> -- Use lambda t to be inlinable with two arguments only.
30943122
case t of
3123+
Nil -> z
30953124
Bin p l r
30963125
| signBranch p -> go (go z l) r -- put negative numbers before
30973126
| otherwise -> go (go z r) l
30983127
_ -> go z t
30993128
where
3100-
go z' Nil = z'
3129+
go _ Nil = error "foldrWithKey.go: Nil"
31013130
go z' (Tip kx x) = f kx x z'
31023131
go z' (Bin _ l r) = go (go z' r) l
31033132
{-# INLINE foldrWithKey #-}
31043133

31053134
-- | \(O(n)\). A strict version of 'foldrWithKey'. Each application of the operator is
31063135
-- evaluated before using the result in the next application. This
31073136
-- function is strict in the starting value.
3137+
3138+
-- See Note [IntMap folds]
31083139
foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b
31093140
foldrWithKey' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
31103141
case t of
3142+
Nil -> z
31113143
Bin p l r
31123144
| signBranch p -> go (go z l) r -- put negative numbers before
31133145
| otherwise -> go (go z r) l
31143146
_ -> go z t
31153147
where
3116-
go !z' Nil = z'
3148+
go !_ Nil = error "foldrWithKey'.go: Nil"
31173149
go z' (Tip kx x) = f kx x z'
31183150
go z' (Bin _ l r) = go (go z' r) l
31193151
{-# INLINE foldrWithKey' #-}
@@ -3128,31 +3160,37 @@ foldrWithKey' f z = \t -> -- Use lambda t to be inlinable with two argument
31283160
--
31293161
-- > let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
31303162
-- > foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
3163+
3164+
-- See Note [IntMap folds]
31313165
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a
31323166
foldlWithKey f z = \t -> -- Use lambda t to be inlinable with two arguments only.
31333167
case t of
3168+
Nil -> z
31343169
Bin p l r
31353170
| signBranch p -> go (go z r) l -- put negative numbers before
31363171
| otherwise -> go (go z l) r
31373172
_ -> go z t
31383173
where
3139-
go z' Nil = z'
3174+
go _ Nil = error "foldlWithKey.go: Nil"
31403175
go z' (Tip kx x) = f z' kx x
31413176
go z' (Bin _ l r) = go (go z' l) r
31423177
{-# INLINE foldlWithKey #-}
31433178

31443179
-- | \(O(n)\). A strict version of 'foldlWithKey'. Each application of the operator is
31453180
-- evaluated before using the result in the next application. This
31463181
-- function is strict in the starting value.
3182+
3183+
-- See Note [IntMap folds]
31473184
foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a
31483185
foldlWithKey' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
31493186
case t of
3187+
Nil -> z
31503188
Bin p l r
31513189
| signBranch p -> go (go z r) l -- put negative numbers before
31523190
| otherwise -> go (go z l) r
31533191
_ -> go z t
31543192
where
3155-
go !z' Nil = z'
3193+
go !_ Nil = error "foldlWithKey'.go: Nil"
31563194
go z' (Tip kx x) = f z' kx x
31573195
go z' (Bin _ l r) = go (go z' l) r
31583196
{-# INLINE foldlWithKey' #-}
@@ -3164,14 +3202,29 @@ foldlWithKey' f z = \t -> -- Use lambda t to be inlinable with two argument
31643202
-- This can be an asymptotically faster than 'foldrWithKey' or 'foldlWithKey' for some monoids.
31653203
--
31663204
-- @since 0.5.4
3205+
3206+
-- See Note [IntMap folds]
31673207
foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m
3168-
foldMapWithKey f = go
3208+
foldMapWithKey f = \t -> -- Use lambda to be inlinable with two arguments.
3209+
case t of
3210+
Nil -> mempty
3211+
Bin p l r
3212+
#if MIN_VERSION_base(4,11,0)
3213+
| signBranch p -> go r <> go l
3214+
| otherwise -> go l <> go r
3215+
#else
3216+
| signBranch p -> go r `mappend` go l
3217+
| otherwise -> go l `mappend` go r
3218+
#endif
3219+
_ -> go t
31693220
where
3170-
go Nil = mempty
3171-
go (Tip kx x) = f kx x
3172-
go (Bin p l r)
3173-
| signBranch p = go r `mappend` go l
3174-
| otherwise = go l `mappend` go r
3221+
go Nil = error "foldMap.go: Nil"
3222+
go (Tip kx x) = f kx x
3223+
#if MIN_VERSION_base(4,11,0)
3224+
go (Bin _ l r) = go l <> go r
3225+
#else
3226+
go (Bin _ l r) = go l `mappend` go r
3227+
#endif
31753228
{-# INLINE foldMapWithKey #-}
31763229

31773230
{--------------------------------------------------------------------
@@ -4048,3 +4101,40 @@ withEmpty bars = " ":bars
40484101
--
40494102
-- The implementation is defined as a foldl' over the input list, which makes
40504103
-- it a good consumer in list fusion.
4104+
4105+
-- Note [IntMap folds]
4106+
-- ~~~~~~~~~~~~~~~~~~~
4107+
-- Folds on IntMap are defined in a particular way for a few reasons.
4108+
--
4109+
-- foldl' :: (a -> b -> a) -> a -> IntMap b -> a
4110+
-- foldl' f z = \t ->
4111+
-- case t of
4112+
-- Nil -> z
4113+
-- Bin p l r
4114+
-- | signBranch p -> go (go z r) l
4115+
-- | otherwise -> go (go z l) r
4116+
-- _ -> go z t
4117+
-- where
4118+
-- go !_ Nil = error "foldl'.go: Nil"
4119+
-- go z' (Tip _ x) = f z' x
4120+
-- go z' (Bin _ l r) = go (go z' l) r
4121+
-- {-# INLINE foldl' #-}
4122+
--
4123+
-- 1. We first check if the Bin separates negative and positive keys, and fold
4124+
-- over the children accordingly. This check is not inside `go` because it
4125+
-- can only happen at the top level and we don't need to check every Bin.
4126+
-- 2. We also check for Nil at the top level instead of, say, `go z Nil = z`.
4127+
-- That's because `Nil` is also allowed only at the top-level, but more
4128+
-- importantly it allows for better optimizations if the `Nil` branch errors
4129+
-- in `go`. For example, if we have
4130+
-- maximum :: Ord a => IntMap a -> Maybe a
4131+
-- maximum = foldl' (\m x -> Just $! maybe x (max x) m) Nothing
4132+
-- because `go` certainly returns a `Just` (or errors), CPR analysis will
4133+
-- optimize it to return `(# a #)` instead of `Maybe a`. This makes it
4134+
-- satisfy the conditions for SpecConstr, which generates two specializations
4135+
-- of `go` for `Nothing` and `Just` inputs. Now both `Maybe`s have been
4136+
-- optimized out of `go`.
4137+
-- 3. The `Tip` is not matched on at the top-level to avoid using `f` more than
4138+
-- once. This allows `f` to be inlined into `go` even if `f` is big, since
4139+
-- it's likely to be the only place `f` is used, and not inlining `f` means
4140+
-- missing out on optimizations. See GHC #25259 for more on this.

0 commit comments

Comments
 (0)