[commit: ghc] master: Generalise Control.Monad.{sequence_, msum, mapM_, forM_} (b406085)

git at git.haskell.org git at git.haskell.org
Thu Sep 18 21:13:28 UTC 2014


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

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

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

commit b4060858f5201489e11ab57063e72380c03c3b55
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Sep 18 23:05:57 2014 +0200

    Generalise Control.Monad.{sequence_,msum,mapM_,forM_}
    
    This finally takes the gloves off, and performs the first actual
    generalization in order to implement #9586. This re-exports the
    respective definitions for the 4 combinators defined in Data.Foldable.
    
    This way, importing Data.Foldable and Control.Monad unqualified won't bring
    conflicting definitions of those 4 entities into scope anymore.
    
    This change seems to have some minor effect on rule-firing, which
    causes some wibble in the test-case T4007
    
    Reviewed By: ekmett, austin
    
    Differential Revision: https://phabricator.haskell.org/D226


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

b4060858f5201489e11ab57063e72380c03c3b55
 libraries/base/Control/Monad.hs            | 27 ++-------------------------
 testsuite/tests/perf/compiler/T4007.stdout |  5 ++++-
 2 files changed, 6 insertions(+), 26 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 3487a09..eb00939 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -76,12 +76,11 @@ module Control.Monad
     , (<$!>)
     ) where
 
-import Data.Foldable ()
+import Data.Foldable ( sequence_, msum, mapM_, forM_ )
 import Data.Functor ( void )
-import Data.Maybe
 
-import GHC.List
 import GHC.Base
+import GHC.List ( zipWith, unzip, replicate )
 
 -- -----------------------------------------------------------------------------
 -- Prelude monad functions
@@ -94,22 +93,11 @@ sequence ms = foldr k (return []) ms
             where
               k m m' = do { x <- m; xs <- m'; return (x:xs) }
 
--- | Evaluate each action in the sequence from left to right,
--- and ignore the results.
-sequence_        :: Monad m => [m a] -> m ()
-{-# INLINE sequence_ #-}
-sequence_ ms     =  foldr (>>) (return ()) ms
-
 -- | @'mapM' f@ is equivalent to @'sequence' . 'map' f at .
 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
 {-# INLINE mapM #-}
 mapM f as       =  sequence (map f as)
 
--- | @'mapM_' f@ is equivalent to @'sequence_' . 'map' f at .
-mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
-{-# INLINE mapM_ #-}
-mapM_ f as      =  sequence_ (map f as)
-
 -- -----------------------------------------------------------------------------
 -- Functions mandated by the Prelude
 
@@ -133,17 +121,6 @@ forM            :: Monad m => [a] -> (a -> m b) -> m [b]
 {-# INLINE forM #-}
 forM            = flip mapM
 
--- | 'forM_' is 'mapM_' with its arguments flipped
-forM_           :: Monad m => [a] -> (a -> m b) -> m ()
-{-# INLINE forM_ #-}
-forM_           = flip mapM_
-
--- | This generalizes the list-based 'concat' function.
-
-msum        :: MonadPlus m => [m a] -> m a
-{-# INLINE msum #-}
-msum        =  foldr mplus mzero
-
 infixr 1 <=<, >=>
 
 -- | Left-to-right Kleisli composition of monads.
diff --git a/testsuite/tests/perf/compiler/T4007.stdout b/testsuite/tests/perf/compiler/T4007.stdout
index 83a1f16..aabd610 100644
--- a/testsuite/tests/perf/compiler/T4007.stdout
+++ b/testsuite/tests/perf/compiler/T4007.stdout
@@ -1,11 +1,14 @@
 Rule fired: unpack
-Rule fired: Class op return
 Rule fired: Class op >>
+Rule fired: Class op return
+Rule fired: Class op foldr
 Rule fired: Class op >>
 Rule fired: Class op return
+Rule fired: Class op foldr
 Rule fired: Class op >>
 Rule fired: Class op return
 Rule fired: <=#
 Rule fired: tagToEnum#
+Rule fired: Class op foldr
 Rule fired: fold/build
 Rule fired: unpack-list



More information about the ghc-commits mailing list