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