[commit: ghc] master: Eta-expand argument to foldr in mapM_ for [] (7cf87fc)

git at git.haskell.org git at git.haskell.org
Thu Feb 5 23:42:48 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7cf87fc6928f0252d9f61719e2344e6c69237079/ghc

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

commit 7cf87fc6928f0252d9f61719e2344e6c69237079
Author: David Feuer <david.feuer at gmail.com>
Date:   Thu Feb 5 17:42:50 2015 -0600

    Eta-expand argument to foldr in mapM_ for []
    
    Summary:
    This improves performance, at least sometimes--the previous
    implementation can be worse than the version in base 4.7. I
    have not had the time to run benchmarks and such, but `mapM`
    already does this.
    
    Also, inline `mapM_`, like `mapM`.
    
    Reviewers: hvr, nomeata, ekmett, austin
    
    Reviewed By: ekmett, austin
    
    Subscribers: thomie
    
    Projects: #ghc
    
    Differential Revision: https://phabricator.haskell.org/D632
    
    GHC Trac Issues: #10034


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

7cf87fc6928f0252d9f61719e2344e6c69237079
 libraries/base/Data/Foldable.hs | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index a745f66..b8b0973 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -349,7 +349,8 @@ for_ = flip traverse_
 -- As of base 4.8.0.0, 'mapM_' is just 'traverse_', specialized to
 -- 'Monad'.
 mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
-mapM_ f= foldr ((>>) . f) (return ())
+{-# INLINE mapM_ #-}
+mapM_ f = foldr (\m n -> f m >> n) (return ())
 
 -- | 'forM_' is 'mapM_' with its arguments flipped. For a version that
 -- doesn't ignore the results see 'Data.Traversable.forM'.



More information about the ghc-commits mailing list