diff options
author | Herbert Valerio Riedel <hvr@gnu.org> | 2014-09-20 23:43:23 +0200 |
---|---|---|
committer | Herbert Valerio Riedel <hvr@gnu.org> | 2014-09-20 23:47:44 +0200 |
commit | 1812898c0332c6807201938911bb914633267d9d (patch) | |
tree | 50e105ac01d4fca9fa34af50611a81e8784d90e2 /libraries | |
parent | 3daf0023d2dcf7caf85d61f2dc177f8e9421b2fd (diff) | |
download | haskell-1812898c0332c6807201938911bb914633267d9d.tar.gz |
Turn a few existing folds into `Foldable`-methods (#9621)
Turn `toList`, `elem`, `sum`, `product`, `maximum`, and `minimum` into
`Foldable` methods. This helps avoiding regressions (and semantic
differences) while implementing #9586
Reviewed By: austin, dfeuer, ekmett
Differential Revision: https://phabricator.haskell.org/D231
Diffstat (limited to 'libraries')
-rw-r--r-- | libraries/base/Data/Foldable.hs | 76 | ||||
-rw-r--r-- | libraries/base/changelog.md | 3 |
2 files changed, 42 insertions, 37 deletions
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index cb13e5ce7e..726aa6cb24 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -39,21 +39,15 @@ module Data.Foldable ( sequence_, msum, -- ** Specialized folds - toList, concat, concatMap, and, or, any, all, - sum, - product, - maximum, maximumBy, - minimum, minimumBy, -- ** Searches - elem, notElem, find ) where @@ -97,6 +91,8 @@ infix 4 `elem`, `notElem` -- > foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l -- class Foldable t where + {-# MINIMAL foldMap | foldr #-} + -- | Combine the elements of a structure using a monoid. fold :: Monoid m => t m -> m fold = foldMap id @@ -153,7 +149,32 @@ class Foldable t where where mf Nothing y = Just y mf (Just x) y = Just (f x y) - {-# MINIMAL foldMap | foldr #-} + + -- | List of elements of a structure. + toList :: Foldable t => t a -> [a] + {-# INLINE toList #-} + toList t = build (\ c n -> foldr c n t) + + -- | Does the element occur in the structure? + elem :: (Foldable t, Eq a) => a -> t a -> Bool + elem = any . (==) + + -- | The largest element of a non-empty structure. + maximum :: (Foldable t, Ord a) => t a -> a + maximum = foldr1 max + + -- | The least element of a non-empty structure. + minimum :: (Foldable t, Ord a) => t a -> a + minimum = foldr1 min + + -- | The 'sum' function computes the sum of the numbers of a structure. + sum :: Num a => t a -> a + sum = getSum . foldMap Sum + + -- | The 'product' function computes the product of the numbers of a + -- structure. + product :: (Foldable t, Num a) => t a -> a + product = getProduct . foldMap Product -- instances for Prelude types @@ -165,11 +186,17 @@ instance Foldable Maybe where foldl f z (Just x) = f z x instance Foldable [] where - foldr = List.foldr - foldl = List.foldl - foldl' = List.foldl' - foldr1 = List.foldr1 - foldl1 = List.foldl1 + elem = List.elem + foldl = List.foldl + foldl' = List.foldl' + foldl1 = List.foldl1 + foldr = List.foldr + foldr1 = List.foldr1 + maximum = List.maximum + minimum = List.minimum + product = List.product + sum = List.sum + toList = id instance Foldable (Either a) where foldMap _ (Left _) = mempty @@ -257,11 +284,6 @@ msum = foldr mplus mzero -- These use foldr rather than foldMap to avoid repeated concatenation. --- | List of elements of a structure. -toList :: Foldable t => t a -> [a] -{-# INLINE toList #-} -toList t = build (\ c n -> foldr c n t) - -- | The concatenation of all the elements of a container of lists. concat :: Foldable t => t [a] -> [a] concat = fold @@ -291,18 +313,6 @@ any p = getAny . foldMap (Any . p) all :: Foldable t => (a -> Bool) -> t a -> Bool all p = getAll . foldMap (All . p) --- | The 'sum' function computes the sum of the numbers of a structure. -sum :: (Foldable t, Num a) => t a -> a -sum = getSum . foldMap Sum - --- | The 'product' function computes the product of the numbers of a structure. -product :: (Foldable t, Num a) => t a -> a -product = getProduct . foldMap Product - --- | The largest element of a non-empty structure. -maximum :: (Foldable t, Ord a) => t a -> a -maximum = foldr1 max - -- | The largest element of a non-empty structure with respect to the -- given comparison function. maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a @@ -311,10 +321,6 @@ maximumBy cmp = foldr1 max' GT -> x _ -> y --- | The least element of a non-empty structure. -minimum :: (Foldable t, Ord a) => t a -> a -minimum = foldr1 min - -- | The least element of a non-empty structure with respect to the -- given comparison function. minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a @@ -323,10 +329,6 @@ minimumBy cmp = foldr1 min' GT -> y _ -> x --- | Does the element occur in the structure? -elem :: (Foldable t, Eq a) => a -> t a -> Bool -elem = any . (==) - -- | 'notElem' is the negation of 'elem'. notElem :: (Foldable t, Eq a) => a -> t a -> Bool notElem x = not . elem x diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 1dbada01ba..d82d354c91 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -32,6 +32,9 @@ * Set fixity for `Data.Foldable.{elem,notElem}` to match the conventional one set for `Data.List.{elem,notElem}` (#9610) + * Turn `toList`, `elem`, `sum`, `product`, `maximum`, and `minimum` + into `Foldable` methods (#9621) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 |