add Traversable generalizations of mapAccumL and mapAccumR (#2461)
[ghc-base.git] / Data / Foldable.hs
index 1111a37..f2baddf 100644 (file)
@@ -4,7 +4,7 @@
 -- Copyright   :  Ross Paterson 2005
 -- License     :  BSD-style (see the LICENSE file in the distribution)
 --
 -- Copyright   :  Ross Paterson 2005
 -- License     :  BSD-style (see the LICENSE file in the distribution)
 --
--- Maintainer  :  ross@soi.city.ac.uk
+-- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
 -- Portability :  portable
 --
 -- Stability   :  experimental
 -- Portability :  portable
 --
 -- for this module.
 
 module Data.Foldable (
 -- for this module.
 
 module Data.Foldable (
-       -- * Folds
-       Foldable(..),
-       -- ** Special biased folds
-       foldr',
-       foldl',
-       foldrM,
-       foldlM,
-       -- ** Folding actions
-       -- *** Applicative actions
-       traverse_,
-       for_,
-       sequenceA_,
-       asum,
-       -- *** Monadic actions
-       mapM_,
-       forM_,
-       sequence_,
-       msum,
-       -- ** Specialized folds
-       toList,
-       concat,
-       concatMap,
-       and,
-       or,
-       any,
-       all,
-       sum,
-       product,
-       maximum,
-       maximumBy,
-       minimum,
-       minimumBy,
-       -- ** Searches
-       elem,
-       notElem,
-       find
-       ) where
+        -- * Folds
+        Foldable(..),
+        -- ** Special biased folds
+        foldr',
+        foldl',
+        foldrM,
+        foldlM,
+        -- ** Folding actions
+        -- *** Applicative actions
+        traverse_,
+        for_,
+        sequenceA_,
+        asum,
+        -- *** Monadic actions
+        mapM_,
+        forM_,
+        sequence_,
+        msum,
+        -- ** Specialized folds
+        toList,
+        concat,
+        concatMap,
+        and,
+        or,
+        any,
+        all,
+        sum,
+        product,
+        maximum,
+        maximumBy,
+        minimum,
+        minimumBy,
+        -- ** Searches
+        elem,
+        notElem,
+        find
+        ) where
 
 import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
 
 import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
-               elem, notElem, concat, concatMap, and, or, any, all,
-               sum, product, maximum, minimum)
+                elem, notElem, concat, concatMap, and, or, any, all,
+                sum, product, maximum, minimum)
 import qualified Prelude (foldl, foldr, foldl1, foldr1)
 import Control.Applicative
 import Control.Monad (MonadPlus(..))
 import Data.Maybe (fromMaybe, listToMaybe)
 import Data.Monoid
 import qualified Prelude (foldl, foldr, foldl1, foldr1)
 import Control.Applicative
 import Control.Monad (MonadPlus(..))
 import Data.Maybe (fromMaybe, listToMaybe)
 import Data.Monoid
-import Data.Array
+
+#ifdef __NHC__
+import Control.Arrow (ArrowZero(..)) -- work around nhc98 typechecker problem
+#endif
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Exts (build)
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Exts (build)
@@ -88,64 +91,61 @@ import GHC.Exts (build)
 -- to satisfy the monoid laws.
 --
 class Foldable t where
 -- to satisfy the monoid laws.
 --
 class Foldable t where
-       -- | Combine the elements of a structure using a monoid.
-       fold :: Monoid m => t m -> m
-       fold = foldMap id
-
-       -- | Map each element of the structure to a monoid,
-       -- and combine the results.
-       foldMap :: Monoid m => (a -> m) -> t a -> m
-       foldMap f = foldr (mappend . f) mempty
-
-       -- | Right-associative fold of a structure.
-       --
-       -- @'foldr' f z = 'Prelude.foldr' f z . 'toList'@
-       foldr :: (a -> b -> b) -> b -> t a -> b
-       foldr f z t = appEndo (foldMap (Endo . f) t) z
-
-       -- | Left-associative fold of a structure.
-       --
-       -- @'foldl' f z = 'Prelude.foldl' f z . 'toList'@
-       foldl :: (a -> b -> a) -> a -> t b -> a
-       foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
-
-       -- | A variant of 'foldr' that has no base case,
-       -- and thus may only be applied to non-empty structures.
-       --
-       -- @'foldr1' f = 'Prelude.foldr1' f . 'toList'@
-       foldr1 :: (a -> a -> a) -> t a -> a
-       foldr1 f xs = fromMaybe (error "foldr1: empty structure")
-                       (foldr mf Nothing xs)
-         where mf x Nothing = Just x
-               mf x (Just y) = Just (f x y)
-
-       -- | A variant of 'foldl' that has no base case,
-       -- and thus may only be applied to non-empty structures.
-       --
-       -- @'foldl1' f = 'Prelude.foldl1' f . 'toList'@
-       foldl1 :: (a -> a -> a) -> t a -> a
-       foldl1 f xs = fromMaybe (error "foldl1: empty structure")
-                       (foldl mf Nothing xs)
-         where mf Nothing y = Just y
-               mf (Just x) y = Just (f x y)
+        -- | Combine the elements of a structure using a monoid.
+        fold :: Monoid m => t m -> m
+        fold = foldMap id
+
+        -- | Map each element of the structure to a monoid,
+        -- and combine the results.
+        foldMap :: Monoid m => (a -> m) -> t a -> m
+        foldMap f = foldr (mappend . f) mempty
+
+        -- | Right-associative fold of a structure.
+        --
+        -- @'foldr' f z = 'Prelude.foldr' f z . 'toList'@
+        foldr :: (a -> b -> b) -> b -> t a -> b
+        foldr f z t = appEndo (foldMap (Endo . f) t) z
+
+        -- | Left-associative fold of a structure.
+        --
+        -- @'foldl' f z = 'Prelude.foldl' f z . 'toList'@
+        foldl :: (a -> b -> a) -> a -> t b -> a
+        foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
+
+        -- | A variant of 'foldr' that has no base case,
+        -- and thus may only be applied to non-empty structures.
+        --
+        -- @'foldr1' f = 'Prelude.foldr1' f . 'toList'@
+        foldr1 :: (a -> a -> a) -> t a -> a
+        foldr1 f xs = fromMaybe (error "foldr1: empty structure")
+                        (foldr mf Nothing xs)
+          where mf x Nothing = Just x
+                mf x (Just y) = Just (f x y)
+
+        -- | A variant of 'foldl' that has no base case,
+        -- and thus may only be applied to non-empty structures.
+        --
+        -- @'foldl1' f = 'Prelude.foldl1' f . 'toList'@
+        foldl1 :: (a -> a -> a) -> t a -> a
+        foldl1 f xs = fromMaybe (error "foldl1: empty structure")
+                        (foldl mf Nothing xs)
+          where mf Nothing y = Just y
+                mf (Just x) y = Just (f x y)
 
 -- instances for Prelude types
 
 instance Foldable Maybe where
 
 -- instances for Prelude types
 
 instance Foldable Maybe where
-       foldr f z Nothing = z
-       foldr f z (Just x) = f x z
+        foldr f z Nothing = z
+        foldr f z (Just x) = f x z
 
 
-       foldl f z Nothing = z
-       foldl f z (Just x) = f z x
+        foldl f z Nothing = z
+        foldl f z (Just x) = f z x
 
 instance Foldable [] where
 
 instance Foldable [] where
-       foldr = Prelude.foldr
-       foldl = Prelude.foldl
-       foldr1 = Prelude.foldr1
-       foldl1 = Prelude.foldl1
-
-instance Ix i => Foldable (Array i) where
-       foldr f z = Prelude.foldr f z . elems
+        foldr = Prelude.foldr
+        foldl = Prelude.foldl
+        foldr1 = Prelude.foldr1
+        foldl1 = Prelude.foldl1
 
 -- | Fold over the elements of a structure,
 -- associating to the right, but strictly.
 
 -- | Fold over the elements of a structure,
 -- associating to the right, but strictly.
@@ -181,7 +181,7 @@ for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
 {-# INLINE for_ #-}
 for_ = flip traverse_
 
 {-# INLINE for_ #-}
 for_ = flip traverse_
 
--- | Map each element of a structure to an monadic action, evaluate
+-- | Map each element of a structure to a 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 ())
 -- 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 ())
@@ -267,8 +267,8 @@ maximum = foldr1 max
 maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
 maximumBy cmp = foldr1 max'
   where max' x y = case cmp x y of
 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
+                        GT -> x
+                        _  -> y
 
 -- | The least element of a non-empty structure.
 minimum :: (Foldable t, Ord a) => t a -> a
 
 -- | The least element of a non-empty structure.
 minimum :: (Foldable t, Ord a) => t a -> a
@@ -279,8 +279,8 @@ minimum = foldr1 min
 minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
 minimumBy cmp = foldr1 min'
   where min' x y = case cmp x y of
 minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
 minimumBy cmp = foldr1 min'
   where min' x y = case cmp x y of
-                       GT -> y
-                       _  -> x
+                        GT -> y
+                        _  -> x
 
 -- | Does the element occur in the structure?
 elem :: (Foldable t, Eq a) => a -> t a -> Bool
 
 -- | Does the element occur in the structure?
 elem :: (Foldable t, Eq a) => a -> t a -> Bool