[commit: packages/containers] ghc-head: Added `foldMapWithKey`. (40187f3)

git at git.haskell.org git at git.haskell.org
Wed Sep 4 21:24:32 CEST 2013


Repository : ssh://git@git.haskell.org/containers

On branch  : ghc-head
Link       : http://git.haskell.org/?p=packages/containers.git;a=commit;h=40187f32a43689ff02ca2b97465aa4fcd9f9d150

>---------------------------------------------------------------

commit 40187f32a43689ff02ca2b97465aa4fcd9f9d150
Author: Edward Kmett <ekmett at gmail.com>
Date:   Tue Dec 25 05:57:40 2012 -0500

    Added `foldMapWithKey`.


>---------------------------------------------------------------

40187f32a43689ff02ca2b97465aa4fcd9f9d150
 Data/IntMap/Base.hs   |   15 +++++++++++++++
 Data/IntMap/Lazy.hs   |    2 ++
 Data/IntMap/Strict.hs |    2 ++
 Data/Map/Base.hs      |   14 ++++++++++++++
 Data/Map/Lazy.hs      |    2 ++
 Data/Map/Strict.hs    |    2 ++
 6 files changed, 37 insertions(+)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 73b05b2..05dd3fa 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -123,6 +123,8 @@ module Data.IntMap.Base (
     , foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'
@@ -1670,6 +1672,19 @@ foldlWithKey' f z = \t ->      -- Use lambda t to be inlinable with two argument
     go z' (Bin _ _ l r) = go (go z' l) r
 {-# INLINE foldlWithKey' #-}
 
+-- | /O(n)/. Fold the keys and values in the map using the given monoid, such that
+--
+-- @'foldMapWithKey' f = 'Prelude.fold' . 'mapWithKey' f@
+--
+-- This can be an asymptotically faster than 'foldrWithKey' or 'foldlWithKey' for some monoids.
+foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m
+foldMapWithKey f = go
+  where
+    go Nil           = mempty
+    go (Tip kx x)    = f kx x
+    go (Bin _ _ l r) = go l `mappend` go r
+{-# INLINE foldMapWithKey #-}
+
 {--------------------------------------------------------------------
   List variations
 --------------------------------------------------------------------}
diff --git a/Data/IntMap/Lazy.hs b/Data/IntMap/Lazy.hs
index fed6538..6de26f8 100644
--- a/Data/IntMap/Lazy.hs
+++ b/Data/IntMap/Lazy.hs
@@ -133,6 +133,8 @@ module Data.IntMap.Lazy (
     , IM.foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'
diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs
index e6b3708..168d7a8 100644
--- a/Data/IntMap/Strict.hs
+++ b/Data/IntMap/Strict.hs
@@ -139,6 +139,8 @@ module Data.IntMap.Strict (
     , foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 3e240e8..670cdd0 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -169,6 +169,8 @@ module Data.Map.Base (
     , foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'
@@ -1873,6 +1875,18 @@ foldlWithKey' f z = go z
     go z' (Bin _ kx x l r) = go (f (go z' l) kx x) r
 {-# INLINE foldlWithKey' #-}
 
+-- | /O(n)/. Fold the keys and values in the map using the given monoid, such that
+--
+-- @'foldMapWithKey' f = 'Prelude.fold' . 'mapWithKey' f@
+--
+-- This can be an asymptotically faster than 'foldrWithKey' or 'foldlWithKey' for some monoids.
+foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m
+foldMapWithKey f = go
+  where
+    go Tip             = mempty
+    go (Bin _ k v l r) = go l `mappend` f k v `mappend` go r
+{-# INLINE foldMapWithKey #-}
+
 {--------------------------------------------------------------------
   List variations
 --------------------------------------------------------------------}
diff --git a/Data/Map/Lazy.hs b/Data/Map/Lazy.hs
index e637376..1b939f7 100644
--- a/Data/Map/Lazy.hs
+++ b/Data/Map/Lazy.hs
@@ -129,6 +129,8 @@ module Data.Map.Lazy (
     , M.foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'
diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index faa0478..9e91f40 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -136,6 +136,8 @@ module Data.Map.Strict
     , foldl
     , foldrWithKey
     , foldlWithKey
+    , foldMapWithKey
+
     -- ** Strict folds
     , foldr'
     , foldl'





More information about the ghc-commits mailing list