Repository : ssh://darcs.haskell.org//srv/darcs/packages/containers

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7afa9c0b606770927d81a9283885c637fed9c581

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

commit 7afa9c0b606770927d81a9283885c637fed9c581
Author: Milan Straka <[email protected]>
Date:   Wed Dec 7 20:38:57 2011 +0100

    Improve performance of Map.mapKeys[With].
    
    We can manually fuse
      List.map fFirst . toList
        where fFirst (a, b) = (f a, b)
    using the right fold as
      foldrWithKey (\k x xs -> (f k, x) : xs) []

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

 Data/Map/Base.hs   |    6 ++----
 Data/Map/Strict.hs |    4 +---
 2 files changed, 3 insertions(+), 7 deletions(-)

diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 7fc0576..c8382d7 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -219,7 +219,6 @@ module Data.Map.Base (
 
 import Prelude hiding (lookup,map,filter,foldr,foldl,null)
 import qualified Data.Set as Set
-import qualified Data.List as List
 import Data.Monoid (Monoid(..))
 import Control.Applicative (Applicative(..), (<$>))
 import Data.Traversable (Traversable(traverse))
@@ -1494,7 +1493,7 @@ mapAccumRWithKey f a (Bin sx kx x l r) =
 -- > mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == 
singleton 3 "c"
 
 mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a
-mapKeys = mapKeysWith (\x _ -> x)
+mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
 #if __GLASGOW_HASKELL__ >= 700
 {-# INLINABLE mapKeys #-}
 #endif
@@ -1510,8 +1509,7 @@ mapKeys = mapKeysWith (\x _ -> x)
 -- > mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), 
(4,"c")]) == singleton 3 "cdab"
 
 mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a
-mapKeysWith c f = fromListWith c . List.map fFirst . toList
-    where fFirst (x,y) = (f x, y)
+mapKeysWith c f = fromListWith c . foldrWithKey (\k x xs -> (f k, x) : xs) []
 #if __GLASGOW_HASKELL__ >= 700
 {-# INLINABLE mapKeysWith #-}
 #endif
diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index e2ce091..79b44c5 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -223,7 +223,6 @@ module Data.Map.Strict
     ) where
 
 import Prelude hiding (lookup,map,filter,foldr,foldl,null)
-import qualified Data.List as List
 
 import Data.Map.Base hiding
     ( findWithDefault
@@ -966,8 +965,7 @@ mapAccumRWithKey f a (Bin sx kx x l r) =
 -- > mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), 
(4,"c")]) == singleton 3 "cdab"
 
 mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a
-mapKeysWith c f = fromListWith c . List.map fFirst . toList
-    where fFirst (x,y) = (f x, y)
+mapKeysWith c f = fromListWith c . foldrWithKey (\k x xs -> (f k, x) : xs) []
 #if __GLASGOW_HASKELL__ >= 700
 {-# INLINABLE mapKeysWith #-}
 #endif



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to