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