add Data.Foldable.{for_,forM_} and Data.Traversable.{for,forM}
authorRoss Paterson <ross@soi.city.ac.uk>
Wed, 30 Aug 2006 13:38:05 +0000 (13:38 +0000)
committerRoss Paterson <ross@soi.city.ac.uk>
Wed, 30 Aug 2006 13:38:05 +0000 (13:38 +0000)
generalizing Control.Monad.{forM_,forM}

Data/Foldable.hs
Data/Traversable.hs

index e624c1e..28cc6fa 100644 (file)
@@ -26,7 +26,9 @@ module Data.Foldable (
        foldlM,
        -- ** Folding actions
        traverse_,
+       for_,
        mapM_,
+       forM_,
        sequenceA_,
        sequence_,
        -- ** Specialized folds
@@ -169,11 +171,21 @@ foldlM f z xs = foldr f' return xs z
 traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
 traverse_ f = foldr ((*>) . f) (pure ())
 
+-- | 'for_' is 'traverse_' with its arguments flipped.
+for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
+{-# INLINE for_ #-}
+for_ = flip traverse_
+
 -- | Map each element of a structure to an monadic action, evaluate
 -- these actions from left to right, and ignore the results.
 mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
 mapM_ f = foldr ((>>) . f) (return ())
 
+-- | 'forM_' is 'mapM_' with its arguments flipped.
+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.
 sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
index 14edb79..c2c6033 100644 (file)
@@ -29,6 +29,8 @@
 
 module Data.Traversable (
        Traversable(..),
+       for,
+       forM,
        fmapDefault,
        foldMapDefault,
        ) where
@@ -106,6 +108,16 @@ instance Ix i => Traversable (Array i) where
 
 -- general functions
 
+-- | 'for' is 'traverse' with its arguments flipped.
+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 :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
+{-# INLINE forM #-}
+forM = flip mapM
+
 -- | This function may be used as a value for `fmap` in a `Functor` instance.
 fmapDefault :: Traversable t => (a -> b) -> t a -> t b
 fmapDefault f = getId . traverse (Id . f)