@@ -325,7 +325,7 @@ import Data.Bits
325
325
import qualified Data.Foldable as Foldable
326
326
import Data.Maybe (fromMaybe )
327
327
import Utils.Containers.Internal.Prelude hiding
328
- (lookup , map , filter , foldr , foldl , foldl' , null )
328
+ (lookup , map , filter , foldr , foldl , foldl' , foldMap , null )
329
329
import Prelude ()
330
330
331
331
import Data.IntSet.Internal (IntSet )
@@ -469,23 +469,13 @@ instance Semigroup (IntMap a) where
469
469
470
470
-- | Folds in order of increasing key.
471
471
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
478
473
{-# INLINABLE fold #-}
479
474
foldr = foldr
480
475
{-# INLINE foldr #-}
481
476
foldl = foldl
482
477
{-# 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
489
479
{-# INLINE foldMap #-}
490
480
foldl' = foldl'
491
481
{-# INLINE foldl' #-}
@@ -3012,31 +3002,37 @@ splitLookup k t =
3012
3002
--
3013
3003
-- > let f a len = len + (length a)
3014
3004
-- > foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
3005
+
3006
+ -- See Note [IntMap folds]
3015
3007
foldr :: (a -> b -> b ) -> b -> IntMap a -> b
3016
3008
foldr f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3017
3009
case t of
3010
+ Nil -> z
3018
3011
Bin p l r
3019
3012
| signBranch p -> go (go z l) r -- put negative numbers before
3020
3013
| otherwise -> go (go z r) l
3021
3014
_ -> go z t
3022
3015
where
3023
- go z' Nil = z'
3016
+ go _ Nil = error " foldr.go: Nil "
3024
3017
go z' (Tip _ x) = f x z'
3025
3018
go z' (Bin _ l r) = go (go z' r) l
3026
3019
{-# INLINE foldr #-}
3027
3020
3028
3021
-- | \(O(n)\). A strict version of 'foldr'. Each application of the operator is
3029
3022
-- evaluated before using the result in the next application. This
3030
3023
-- function is strict in the starting value.
3024
+
3025
+ -- See Note [IntMap folds]
3031
3026
foldr' :: (a -> b -> b ) -> b -> IntMap a -> b
3032
3027
foldr' f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3033
3028
case t of
3029
+ Nil -> z
3034
3030
Bin p l r
3035
3031
| signBranch p -> go (go z l) r -- put negative numbers before
3036
3032
| otherwise -> go (go z r) l
3037
3033
_ -> go z t
3038
3034
where
3039
- go ! z' Nil = z'
3035
+ go ! _ Nil = error " foldr'.go: Nil "
3040
3036
go z' (Tip _ x) = f x z'
3041
3037
go z' (Bin _ l r) = go (go z' r) l
3042
3038
{-# INLINE foldr' #-}
@@ -3050,35 +3046,65 @@ foldr' f z = \t -> -- Use lambda t to be inlinable with two arguments only.
3050
3046
--
3051
3047
-- > let f len a = len + (length a)
3052
3048
-- > foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
3049
+
3050
+ -- See Note [IntMap folds]
3053
3051
foldl :: (a -> b -> a ) -> a -> IntMap b -> a
3054
3052
foldl f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3055
3053
case t of
3054
+ Nil -> z
3056
3055
Bin p l r
3057
3056
| signBranch p -> go (go z r) l -- put negative numbers before
3058
3057
| otherwise -> go (go z l) r
3059
3058
_ -> go z t
3060
3059
where
3061
- go z' Nil = z'
3060
+ go _ Nil = error " foldl.go: Nil "
3062
3061
go z' (Tip _ x) = f z' x
3063
3062
go z' (Bin _ l r) = go (go z' l) r
3064
3063
{-# INLINE foldl #-}
3065
3064
3066
3065
-- | \(O(n)\). A strict version of 'foldl'. Each application of the operator is
3067
3066
-- evaluated before using the result in the next application. This
3068
3067
-- function is strict in the starting value.
3068
+
3069
+ -- See Note [IntMap folds]
3069
3070
foldl' :: (a -> b -> a ) -> a -> IntMap b -> a
3070
3071
foldl' f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3071
3072
case t of
3073
+ Nil -> z
3072
3074
Bin p l r
3073
3075
| signBranch p -> go (go z r) l -- put negative numbers before
3074
3076
| otherwise -> go (go z l) r
3075
3077
_ -> go z t
3076
3078
where
3077
- go ! z' Nil = z'
3079
+ go ! _ Nil = error " foldl'.go: Nil "
3078
3080
go z' (Tip _ x) = f z' x
3079
3081
go z' (Bin _ l r) = go (go z' l) r
3080
3082
{-# INLINE foldl' #-}
3081
3083
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
+
3082
3108
-- | \(O(n)\). Fold the keys and values in the map using the given right-associative
3083
3109
-- binary operator, such that
3084
3110
-- @'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.
3089
3115
--
3090
3116
-- > let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
3091
3117
-- > foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
3118
+
3119
+ -- See Note [IntMap folds]
3092
3120
foldrWithKey :: (Key -> a -> b -> b ) -> b -> IntMap a -> b
3093
3121
foldrWithKey f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3094
3122
case t of
3123
+ Nil -> z
3095
3124
Bin p l r
3096
3125
| signBranch p -> go (go z l) r -- put negative numbers before
3097
3126
| otherwise -> go (go z r) l
3098
3127
_ -> go z t
3099
3128
where
3100
- go z' Nil = z'
3129
+ go _ Nil = error " foldrWithKey.go: Nil "
3101
3130
go z' (Tip kx x) = f kx x z'
3102
3131
go z' (Bin _ l r) = go (go z' r) l
3103
3132
{-# INLINE foldrWithKey #-}
3104
3133
3105
3134
-- | \(O(n)\). A strict version of 'foldrWithKey'. Each application of the operator is
3106
3135
-- evaluated before using the result in the next application. This
3107
3136
-- function is strict in the starting value.
3137
+
3138
+ -- See Note [IntMap folds]
3108
3139
foldrWithKey' :: (Key -> a -> b -> b ) -> b -> IntMap a -> b
3109
3140
foldrWithKey' f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3110
3141
case t of
3142
+ Nil -> z
3111
3143
Bin p l r
3112
3144
| signBranch p -> go (go z l) r -- put negative numbers before
3113
3145
| otherwise -> go (go z r) l
3114
3146
_ -> go z t
3115
3147
where
3116
- go ! z' Nil = z'
3148
+ go ! _ Nil = error " foldrWithKey'.go: Nil "
3117
3149
go z' (Tip kx x) = f kx x z'
3118
3150
go z' (Bin _ l r) = go (go z' r) l
3119
3151
{-# INLINE foldrWithKey' #-}
@@ -3128,31 +3160,37 @@ foldrWithKey' f z = \t -> -- Use lambda t to be inlinable with two argument
3128
3160
--
3129
3161
-- > let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
3130
3162
-- > foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
3163
+
3164
+ -- See Note [IntMap folds]
3131
3165
foldlWithKey :: (a -> Key -> b -> a ) -> a -> IntMap b -> a
3132
3166
foldlWithKey f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3133
3167
case t of
3168
+ Nil -> z
3134
3169
Bin p l r
3135
3170
| signBranch p -> go (go z r) l -- put negative numbers before
3136
3171
| otherwise -> go (go z l) r
3137
3172
_ -> go z t
3138
3173
where
3139
- go z' Nil = z'
3174
+ go _ Nil = error " foldlWithKey.go: Nil "
3140
3175
go z' (Tip kx x) = f z' kx x
3141
3176
go z' (Bin _ l r) = go (go z' l) r
3142
3177
{-# INLINE foldlWithKey #-}
3143
3178
3144
3179
-- | \(O(n)\). A strict version of 'foldlWithKey'. Each application of the operator is
3145
3180
-- evaluated before using the result in the next application. This
3146
3181
-- function is strict in the starting value.
3182
+
3183
+ -- See Note [IntMap folds]
3147
3184
foldlWithKey' :: (a -> Key -> b -> a ) -> a -> IntMap b -> a
3148
3185
foldlWithKey' f z = \ t -> -- Use lambda t to be inlinable with two arguments only.
3149
3186
case t of
3187
+ Nil -> z
3150
3188
Bin p l r
3151
3189
| signBranch p -> go (go z r) l -- put negative numbers before
3152
3190
| otherwise -> go (go z l) r
3153
3191
_ -> go z t
3154
3192
where
3155
- go ! z' Nil = z'
3193
+ go ! _ Nil = error " foldlWithKey'.go: Nil "
3156
3194
go z' (Tip kx x) = f z' kx x
3157
3195
go z' (Bin _ l r) = go (go z' l) r
3158
3196
{-# INLINE foldlWithKey' #-}
@@ -3164,14 +3202,29 @@ foldlWithKey' f z = \t -> -- Use lambda t to be inlinable with two argument
3164
3202
-- This can be an asymptotically faster than 'foldrWithKey' or 'foldlWithKey' for some monoids.
3165
3203
--
3166
3204
-- @since 0.5.4
3205
+
3206
+ -- See Note [IntMap folds]
3167
3207
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
3169
3220
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
3175
3228
{-# INLINE foldMapWithKey #-}
3176
3229
3177
3230
{- -------------------------------------------------------------------
@@ -4048,3 +4101,40 @@ withEmpty bars = " ":bars
4048
4101
--
4049
4102
-- The implementation is defined as a foldl' over the input list, which makes
4050
4103
-- 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