add Data.Foldable.{for_,forM_} and Data.Traversable.{for,forM}
[haskell-directory.git] / Data / Foldable.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Foldable
4 -- Copyright   :  Ross Paterson 2005
5 -- License     :  BSD-style (see the LICENSE file in the distribution)
6 --
7 -- Maintainer  :  ross@soi.city.ac.uk
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- Class of data structures that can be folded to a summary value.
12 --
13 -- Many of these functions generalize "Prelude" and "Data.List"
14 -- functions of the same names from lists to any 'Foldable' functor.
15 -- To avoid ambiguity, either import the "Prelude" and "Data.List"
16 -- hiding these names or qualify uses of these function names with an
17 -- alias for this module.
18
19 module Data.Foldable (
20         -- * Folds
21         Foldable(..),
22         -- ** Special biased folds
23         foldr',
24         foldl',
25         foldrM,
26         foldlM,
27         -- ** Folding actions
28         traverse_,
29         for_,
30         mapM_,
31         forM_,
32         sequenceA_,
33         sequence_,
34         -- ** Specialized folds
35         toList,
36         concat,
37         concatMap,
38         and,
39         or,
40         any,
41         all,
42         sum,
43         product,
44         maximum,
45         maximumBy,
46         minimum,
47         minimumBy,
48         -- ** Searches
49         elem,
50         notElem,
51         find
52         ) where
53
54 import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
55                 elem, notElem, concat, concatMap, and, or, any, all,
56                 sum, product, maximum, minimum)
57 import qualified Prelude (foldl, foldr, foldl1, foldr1)
58 import Control.Applicative
59 import Data.Maybe (fromMaybe, listToMaybe)
60 import Data.Monoid
61 import Data.Array
62
63 #ifdef __GLASGOW_HASKELL__
64 import GHC.Exts (build)
65 #endif
66
67 -- | Data structures that can be folded.
68 --
69 -- Minimal complete definition: 'foldMap' or 'foldr'.
70 --
71 -- For example, given a data type
72 --
73 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
74 --
75 -- a suitable instance would be
76 --
77 -- > instance Foldable Tree
78 -- >    foldMap f Empty = mempty
79 -- >    foldMap f (Leaf x) = f x
80 -- >    foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
81 --
82 -- This is suitable even for abstract types, as the monoid is assumed
83 -- to satisfy the monoid laws.
84 --
85 class Foldable t where
86         -- | Combine the elements of a structure using a monoid.
87         fold :: Monoid m => t m -> m
88         fold = foldMap id
89
90         -- | Map each element of the structure to a monoid,
91         -- and combine the results.
92         foldMap :: Monoid m => (a -> m) -> t a -> m
93         foldMap f = foldr (mappend . f) mempty
94
95         -- | Right-associative fold of a structure.
96         --
97         -- @'foldr' f z = 'Prelude.foldr' f z . 'toList'@
98         foldr :: (a -> b -> b) -> b -> t a -> b
99         foldr f z t = appEndo (foldMap (Endo . f) t) z
100
101         -- | Left-associative fold of a structure.
102         --
103         -- @'foldl' f z = 'Prelude.foldl' f z . 'toList'@
104         foldl :: (a -> b -> a) -> a -> t b -> a
105         foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
106
107         -- | A variant of 'foldr' that has no base case,
108         -- and thus may only be applied to non-empty structures.
109         --
110         -- @'foldr1' f = 'Prelude.foldr1' f . 'toList'@
111         foldr1 :: (a -> a -> a) -> t a -> a
112         foldr1 f xs = fromMaybe (error "foldr1: empty structure")
113                         (foldr mf Nothing xs)
114           where mf x Nothing = Just x
115                 mf x (Just y) = Just (f x y)
116
117         -- | A variant of 'foldl' that has no base case,
118         -- and thus may only be applied to non-empty structures.
119         --
120         -- @'foldl1' f = 'Prelude.foldl1' f . 'toList'@
121         foldl1 :: (a -> a -> a) -> t a -> a
122         foldl1 f xs = fromMaybe (error "foldl1: empty structure")
123                         (foldl mf Nothing xs)
124           where mf Nothing y = Just y
125                 mf (Just x) y = Just (f x y)
126
127 -- instances for Prelude types
128
129 instance Foldable Maybe where
130         foldr f z Nothing = z
131         foldr f z (Just x) = f x z
132
133         foldl f z Nothing = z
134         foldl f z (Just x) = f z x
135
136 instance Foldable [] where
137         foldr = Prelude.foldr
138         foldl = Prelude.foldl
139         foldr1 = Prelude.foldr1
140         foldl1 = Prelude.foldl1
141
142 instance Ix i => Foldable (Array i) where
143         foldr f z = Prelude.foldr f z . elems
144
145 -- | Fold over the elements of a structure,
146 -- associating to the right, but strictly.
147 foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b
148 foldr' f z xs = foldl f' id xs z
149   where f' k x z = k $! f x z
150
151 -- | Monadic fold over the elements of a structure,
152 -- associating to the right, i.e. from right to left.
153 foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
154 foldrM f z xs = foldl f' return xs z
155   where f' k x z = f x z >>= k
156
157 -- | Fold over the elements of a structure,
158 -- associating to the left, but strictly.
159 foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a
160 foldl' f z xs = foldr f' id xs z
161   where f' x k z = k $! f z x
162
163 -- | Monadic fold over the elements of a structure,
164 -- associating to the left, i.e. from left to right.
165 foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a
166 foldlM f z xs = foldr f' return xs z
167   where f' x k z = f z x >>= k
168
169 -- | Map each element of a structure to an action, evaluate
170 -- these actions from left to right, and ignore the results.
171 traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
172 traverse_ f = foldr ((*>) . f) (pure ())
173
174 -- | 'for_' is 'traverse_' with its arguments flipped.
175 for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
176 {-# INLINE for_ #-}
177 for_ = flip traverse_
178
179 -- | Map each element of a structure to an monadic action, evaluate
180 -- these actions from left to right, and ignore the results.
181 mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
182 mapM_ f = foldr ((>>) . f) (return ())
183
184 -- | 'forM_' is 'mapM_' with its arguments flipped.
185 forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
186 {-# INLINE forM_ #-}
187 forM_ = flip mapM_
188
189 -- | Evaluate each action in the structure from left to right,
190 -- and ignore the results.
191 sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
192 sequenceA_ = foldr (*>) (pure ())
193
194 -- | Evaluate each monadic action in the structure from left to right,
195 -- and ignore the results.
196 sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
197 sequence_ = foldr (>>) (return ())
198
199 -- These use foldr rather than foldMap to avoid repeated concatenation.
200
201 -- | List of elements of a structure.
202 toList :: Foldable t => t a -> [a]
203 #ifdef __GLASGOW_HASKELL__
204 toList t = build (\ c n -> foldr c n t)
205 #else
206 toList = foldr (:) []
207 #endif
208
209 -- | The concatenation of all the elements of a container of lists.
210 concat :: Foldable t => t [a] -> [a]
211 concat = foldr (++) []
212
213 concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
214 concatMap f = foldr ((++) . f) []
215
216 -- | 'and' returns the conjunction of a container of Bools.  For the
217 -- result to be 'True', the container must be finite; 'False', however,
218 -- results from a 'False' value finitely far from the left end.
219 and :: Foldable t => t Bool -> Bool
220 and = getAll . foldMap All
221
222 -- | 'or' returns the disjunction of a container of Bools.  For the
223 -- result to be 'False', the container must be finite; 'True', however,
224 -- results from a 'True' value finitely far from the left end.
225 or :: Foldable t => t Bool -> Bool
226 or = getAny . foldMap Any
227
228 -- | Determines whether any element of the structure satisfies the predicate.
229 any :: Foldable t => (a -> Bool) -> t a -> Bool
230 any p = getAny . foldMap (Any . p)
231
232 -- | Determines whether all elements of the structure satisfy the predicate.
233 all :: Foldable t => (a -> Bool) -> t a -> Bool
234 all p = getAll . foldMap (All . p)
235
236 -- | The 'sum' function computes the sum of the numbers of a structure.
237 sum :: (Foldable t, Num a) => t a -> a
238 sum = getSum . foldMap Sum
239
240 -- | The 'product' function computes the product of the numbers of a structure.
241 product :: (Foldable t, Num a) => t a -> a
242 product = getProduct . foldMap Product
243
244 -- | The largest element of the structure.
245 maximum :: (Foldable t, Ord a) => t a -> a
246 maximum = foldr1 max
247
248 maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
249 maximumBy cmp = foldr1 max'
250   where max' x y = case cmp x y of
251                         GT -> x
252                         _  -> y
253
254 -- | The least element of the structure.
255 minimum :: (Foldable t, Ord a) => t a -> a
256 minimum = foldr1 min
257
258 minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
259 minimumBy cmp = foldr1 min'
260   where min' x y = case cmp x y of
261                         GT -> y
262                         _  -> x
263
264 -- | Does the element occur in the structure?
265 elem :: (Foldable t, Eq a) => a -> t a -> Bool
266 elem = any . (==)
267
268 notElem :: (Foldable t, Eq a) => a -> t a -> Bool
269 notElem x = not . elem x
270
271 -- | The 'find' function takes a predicate and a structure and returns
272 -- the leftmost element of the structure matching the predicate, or
273 -- 'Nothing' if there is no such element.
274 find :: Foldable t => (a -> Bool) -> t a -> Maybe a
275 find p = listToMaybe . concatMap (\ x -> if p x then [x] else [])