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