[commit: ghc] master: base: define `sequence = mapM id` (c016e6f)

git at git.haskell.org git at git.haskell.org
Thu Nov 13 08:06:43 UTC 2014


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

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

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

commit c016e6f74e26708586352fec657798f271b0675b
Author: David Feuer <David.Feuer at gmail.com>
Date:   Thu Nov 13 09:05:22 2014 +0100

    base: define `sequence = mapM id`
    
    This avoids duplication in `GHC.Base`; originally, we had
    
      mapM f = sequence . map f
    
    This led to excessive allocation in `cryptarithm2`. Defining
    
      sequence = mapM id
    
    does not appear to cause any `nofib` problems.
    
    Reviewed By: hvr
    
    Differential Revision: https://phabricator.haskell.org/D470


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

c016e6f74e26708586352fec657798f271b0675b
 libraries/base/GHC/Base.hs | 22 +++++++++++++++++++---
 1 file changed, 19 insertions(+), 3 deletions(-)

diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 397e2b7..f2a447d 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -518,9 +518,8 @@ when p s  = if p then s else pure ()
 -- and collect the results.
 sequence :: Monad m => [m a] -> m [a]
 {-# INLINE sequence #-}
-sequence ms = foldr k (return []) ms
-            where
-              k m m' = do { x <- m; xs <- m'; return (x:xs) }
+sequence = mapM id
+-- Note: [sequence and mapM]
 
 -- | @'mapM' f@ is equivalent to @'sequence' . 'map' f at .
 mapM :: Monad m => (a -> m b) -> [a] -> m [b]
@@ -529,6 +528,23 @@ mapM f as = foldr k (return []) as
             where
               k a r = do { x <- f a; xs <- r; return (x:xs) }
 
+{-
+Note: [sequence and mapM]
+~~~~~~~~~~~~~~~~~~~~~~~~~
+Originally, we defined
+
+mapM f = sequence . map f
+
+This relied on list fusion to produce efficient code for mapM, and led to
+excessive allocation in cryptarithm2. Defining
+
+sequence = mapM id
+
+relies only on inlining a tiny function (id) and beta reduction, which tends to
+be a more reliable aspect of simplification. Indeed, this does not lead to
+similar problems in nofib.
+-}
+
 -- | Promote a function to a monad.
 liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
 liftM f m1              = do { x1 <- m1; return (f x1) }



More information about the ghc-commits mailing list