Skip to content

Commit 7a5a669

Browse files
committed
Implement Data.Map.foldrWithKeyM
1 parent 3406f8b commit 7a5a669

File tree

1 file changed

+19
-1
lines changed

1 file changed

+19
-1
lines changed

containers/src/Data/Map/Internal.hs

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -264,6 +264,7 @@ module Data.Map.Internal (
264264

265265
-- ** Monadic folds
266266
, foldlWithKeyM
267+
, foldrWithKeyM
267268

268269
-- * Conversion
269270
, elems
@@ -3366,16 +3367,33 @@ foldlWithKey' f z = go z
33663367
{-# INLINE foldlWithKey' #-}
33673368

33683369
-- | /O(n)/. Monadic variant of 'foldlWithKey'.
3370+
--
3371+
-- > 'foldlWithKeyM\'' f z0 (fromList [(0,'a'),(1,'b'),(2,'c')]) =
3372+
-- > f z0 0 'a' >>= (\z1 -> f z1 1 'b' >>= (\z2 -> f z2 2 'c'))
33693373
foldlWithKeyM :: Monad m => (a -> k -> b -> m a) -> a -> Map k b -> m a
33703374
foldlWithKeyM f z = go z
33713375
where
3372-
go z' Tip = return z'
3376+
go z' Tip = return z'
33733377
go z' (Bin _ kx x l r) = do
33743378
z'' <- go z' l
33753379
z''' <- f z'' kx x
33763380
go z''' r
33773381
{-# INLINE foldlWithKeyM #-}
33783382

3383+
-- | /O(n)/. Monadic variant of 'foldrWithKey'.
3384+
--
3385+
-- > 'foldrWithKeyM\'' f z0 (fromList [(0,'a'),(1,'b'),(2,'c')]) =
3386+
-- > (f 2 'c' >=> f 1 'b' >=> f 0 'a') z0
3387+
foldrWithKeyM :: Monad m => (k -> a -> b -> m b) -> b -> Map k a -> m b
3388+
foldrWithKeyM f z = go z
3389+
where
3390+
go z' Tip = return z'
3391+
go z' (Bin _ kx x l r) = do
3392+
z'' <- go z' r
3393+
z''' <- f kx x z''
3394+
go z''' l
3395+
{-# INLINE foldrWithKeyM #-}
3396+
33793397
-- | /O(n)/. Fold the keys and values in the map using the given monoid, such that
33803398
--
33813399
-- @'foldMapWithKey' f = 'Prelude.fold' . 'mapWithKey' f@

0 commit comments

Comments
 (0)