[commit: ghc] master: Revert "Eta-expand argument to foldr in mapM_ for []" (91d9530)
git at git.haskell.org
git at git.haskell.org
Wed Feb 18 15:48:19 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/91d9530525803403c3c012901115d54ff4fc3b5e/ghc
>---------------------------------------------------------------
commit 91d9530525803403c3c012901115d54ff4fc3b5e
Author: Austin Seipp <austin at well-typed.com>
Date: Tue Feb 17 09:08:12 2015 -0600
Revert "Eta-expand argument to foldr in mapM_ for []"
This change lacked justification (or a test!) for its improvements, and
I merged it on a sweep of Phabricator without fixing this. Trac #10034.
This reverts commit 7cf87fc6928f0252d9f61719e2344e6c69237079.
>---------------------------------------------------------------
91d9530525803403c3c012901115d54ff4fc3b5e
libraries/base/Data/Foldable.hs | 3 +--
1 file changed, 1 insertion(+), 2 deletions(-)
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index b8b0973..a745f66 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -349,8 +349,7 @@ 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 ()
-{-# INLINE mapM_ #-}
-mapM_ f = foldr (\m n -> f m >> n) (return ())
+mapM_ f= foldr ((>>) . f) (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