import Control.Arrow.ArrowZero to help nhc98's type checker
[haskell-directory.git] / Data / Foldable.hs
index 01eff04..7c34b77 100644 (file)
@@ -9,6 +9,12 @@
 -- Portability :  portable
 --
 -- Class of data structures that can be folded to a summary value.
+--
+-- Many of these functions generalize "Prelude", "Control.Monad" and
+-- "Data.List" functions of the same names from lists to any 'Foldable'
+-- functor.  To avoid ambiguity, either import those modules hiding
+-- these names or qualify uses of these function names with an alias
+-- for this module.
 
 module Data.Foldable (
        -- * Folds
@@ -19,10 +25,16 @@ module Data.Foldable (
        foldrM,
        foldlM,
        -- ** Folding actions
+       -- *** Applicative actions
        traverse_,
-       mapM_,
+       for_,
        sequenceA_,
+       asum,
+       -- *** Monadic actions
+       mapM_,
+       forM_,
        sequence_,
+       msum,
        -- ** Specialized folds
        toList,
        concat,
@@ -47,7 +59,9 @@ import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
                elem, notElem, concat, concatMap, and, or, any, all,
                sum, product, maximum, minimum)
 import qualified Prelude (foldl, foldr, foldl1, foldr1)
+import Control.Arrow (ArrowZero(..))
 import Control.Applicative
+import Control.Monad (MonadPlus(..))
 import Data.Maybe (fromMaybe, listToMaybe)
 import Data.Monoid
 import Data.Array
@@ -163,11 +177,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 ()
@@ -178,6 +202,16 @@ sequenceA_ = foldr (*>) (pure ())
 sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
 sequence_ = foldr (>>) (return ())
 
+-- | The sum of a collection of actions, generalizing 'concat'.
+asum :: (Foldable t, Alternative f) => t (f a) -> f a
+{-# INLINE asum #-}
+asum = foldr (<|>) empty
+
+-- | The sum of a collection of actions, generalizing 'concat'.
+msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
+{-# INLINE msum #-}
+msum = foldr mplus mzero
+
 -- These use foldr rather than foldMap to avoid repeated concatenation.
 
 -- | List of elements of a structure.
@@ -190,10 +224,12 @@ toList = foldr (:) []
 
 -- | The concatenation of all the elements of a container of lists.
 concat :: Foldable t => t [a] -> [a]
-concat = foldr (++) []
+concat = fold
 
+-- | Map a function over all the elements of a container and concatenate
+-- the resulting lists.
 concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
-concatMap f = foldr ((++) . f) []
+concatMap = foldMap
 
 -- | 'and' returns the conjunction of a container of Bools.  For the
 -- result to be 'True', the container must be finite; 'False', however,
@@ -223,20 +259,24 @@ sum = getSum . foldMap Sum
 product :: (Foldable t, Num a) => t a -> a
 product = getProduct . foldMap Product
 
--- | The largest element of the structure.
+-- | The largest element of a non-empty structure.
 maximum :: (Foldable t, Ord a) => t a -> a
 maximum = foldr1 max
 
+-- | The largest element of a non-empty structure with respect to the
+-- given comparison function.
 maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
 maximumBy cmp = foldr1 max'
   where max' x y = case cmp x y of
                        GT -> x
                        _  -> y
 
--- | The least element of the structure.
+-- | The least element of a non-empty structure.
 minimum :: (Foldable t, Ord a) => t a -> a
 minimum = foldr1 min
 
+-- | The least element of a non-empty structure with respect to the
+-- given comparison function.
 minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
 minimumBy cmp = foldr1 min'
   where min' x y = case cmp x y of
@@ -247,6 +287,7 @@ minimumBy cmp = foldr1 min'
 elem :: (Foldable t, Eq a) => a -> t a -> Bool
 elem = any . (==)
 
+-- | 'notElem' is the negation of 'elem'.
 notElem :: (Foldable t, Eq a) => a -> t a -> Bool
 notElem x = not . elem x