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