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