[commit: ghc] master: Add references between Data.Traversable.for and Data.Foldable.for_ and co. (d80022d)

git at git.haskell.org git at git.haskell.org
Sat Dec 6 00:35:57 UTC 2014


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

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

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

commit d80022d788cb6dc511d16cb12972265b058a292d
Author: Baldur Blöndal <baldurpet at gmail.com>
Date:   Fri Dec 5 15:15:04 2014 -0600

    Add references between Data.Traversable.for and Data.Foldable.for_ and co.
    
    Summary: This is an issue that sometimes comes up, see
    https://www.haskell.org/pipermail/libraries/2013-May/019872.html
    
    Reviewers: hvr, ekmett, dfeuer, Mikolaj, austin
    
    Reviewed By: ekmett, Mikolaj, austin
    
    Subscribers: mjo
    
    Projects: #ghc
    
    Differential Revision: https://phabricator.haskell.org/D475


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

d80022d788cb6dc511d16cb12972265b058a292d
 libraries/base/Data/Foldable.hs    | 40 +++++++++++++++++++++++++++-----------
 libraries/base/Data/Traversable.hs | 23 ++++++++++++++--------
 2 files changed, 44 insertions(+), 19 deletions(-)

diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index e9246f9..ed32879 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -323,36 +323,54 @@ foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
 foldlM f z0 xs = foldr f' return xs z0
   where f' x k z = f z x >>= k
 
--- | Map each element of a structure to an action, evaluate
--- these actions from left to right, and ignore the results.
+-- | Map each element of a structure to an action, evaluate these
+-- actions from left to right, and ignore the results. For a version
+-- that doesn't ignore the results see 'Data.Traversable.traverse'.
 traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
 traverse_ f = foldr ((*>) . f) (pure ())
 
--- | 'for_' is 'traverse_' with its arguments flipped.
+-- | 'for_' is 'traverse_' with its arguments flipped. For a version
+-- that doesn't ignore the results see 'Data.Traversable.for'.
+--
+-- >>> for_ [1..4] print
+-- 1
+-- 2
+-- 3
+-- 4
 for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
 {-# INLINE for_ #-}
 for_ = flip traverse_
 
 -- | Map each element of a structure to a monadic action, evaluate
--- these actions from left to right, and ignore the results. As of
--- base 4.8.0.0, 'mapM_' is just 'traverse_', specialized to 'Monad'.
+-- these actions from left to right, and ignore the results. For a
+-- version that doesn't ignore the results see
+-- 'Data.Traversable.mapM'.
+--
+-- 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 ())
 
--- | 'forM_' is 'mapM_' with its arguments flipped. As of base
--- 4.8.0.0, 'forM_' is just 'for_', specialized to 'Monad'.
+-- | 'forM_' is 'mapM_' with its arguments flipped. For a version that
+-- doesn't ignore the results see 'Data.Traversable.forM'.
+--
+-- As of base 4.8.0.0, 'forM_' is just 'for_', specialized to 'Monad'.
 forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
 {-# INLINE forM_ #-}
 forM_ = flip mapM_
 
--- | Evaluate each action in the structure from left to right,
--- and ignore the results.
+-- | Evaluate each action in the structure from left to right, and
+-- ignore the results. For a version that doesn't ignore the results
+-- see 'Data.Traversable.sequenceA'.
 sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
 sequenceA_ = foldr (*>) (pure ())
 
 -- | Evaluate each monadic action in the structure from left to right,
--- and ignore the results. As of base 4.8.0.0, 'sequence_' is just
--- 'sequenceA_', specialized to 'Monad'.
+-- and ignore the results. For a version that doesn't ignore the
+-- results see 'Data.Traversable.sequence'.
+--
+-- As of base 4.8.0.0, 'sequence_' is just 'sequenceA_', specialized
+-- to 'Monad'.
 sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
 sequence_ = foldr (>>) (return ())
 
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index f64d99f..e7caf4e 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -144,23 +144,28 @@ import qualified GHC.List as List ( foldr )
 class (Functor t, Foldable t) => Traversable t where
     {-# MINIMAL traverse | sequenceA #-}
 
-    -- | Map each element of a structure to an action, evaluate
+    -- | Map each element of a structure to an action, evaluate these
     -- these actions from left to right, and collect the results.
+    -- actions from left to right, and collect the results. For a
+    -- version that ignores the results see 'Data.Foldable.traverse_'.
     traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
     traverse f = sequenceA . fmap f
 
-    -- | Evaluate each action in the structure from left to right,
-    -- and collect the results.
+    -- | Evaluate each action in the structure from left to right, and
+    -- and collect the results. For a version that ignores the results
+    -- see 'Data.Foldable.sequenceA_'.
     sequenceA :: Applicative f => t (f a) -> f (t a)
     sequenceA = traverse id
 
     -- | Map each element of a structure to a monadic action, evaluate
-    -- these actions from left to right, and collect the results.
+    -- these actions from left to right, and collect the results. For
+    -- a version that ignores the results see 'Data.Foldable.mapM_'.
     mapM :: Monad m => (a -> m b) -> t a -> m (t b)
     mapM = traverse
 
-    -- | Evaluate each monadic action in the structure from left to right,
-    -- and collect the results.
+    -- | Evaluate each monadic action in the structure from left to
+    -- right, and collect the results. For a version that ignores the
+    -- results see 'Data.Foldable.sequence_'.
     sequence :: Monad m => t (m a) -> m (t a)
     sequence = sequenceA
 
@@ -202,12 +207,14 @@ instance Traversable (Const m) where
 
 -- general functions
 
--- | 'for' is 'traverse' with its arguments flipped.
+-- | 'for' is 'traverse' with its arguments flipped. For a version
+-- that ignores the results see 'Data.Foldable.for_'.
 for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
 {-# INLINE for #-}
 for = flip traverse
 
--- | 'forM' is 'mapM' with its arguments flipped.
+-- | 'forM' is 'mapM' with its arguments flipped. For a version that
+-- ignores the results see 'Data.Foldable.forM_'.
 forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
 {-# INLINE forM #-}
 forM = flip mapM



More information about the ghc-commits mailing list