[Git][ghc/ghc][master] 3 commits: Optimisations in Data.Foldable (T17867)
Marge Bot
gitlab at gitlab.haskell.org
Tue Dec 1 00:47:47 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
49ebe369 by chessai at 2020-11-30T19:47:40-05:00
Optimisations in Data.Foldable (T17867)
This PR concerns the following functions from `Data.Foldable`:
* minimum
* maximum
* sum
* product
* minimumBy
* maximumBy
- Default implementations of these functions now use `foldl'` or `foldMap'`.
- All have been marked with INLINEABLE to make room for further optimisations.
- - - - -
4d79ef65 by chessai at 2020-11-30T19:47:40-05:00
Apply suggestion to libraries/base/Data/Foldable.hs
- - - - -
6af074ce by chessai at 2020-11-30T19:47:40-05:00
Apply suggestion to libraries/base/Data/Foldable.hs
- - - - -
1 changed file:
- libraries/base/Data/Foldable.hs
Changes:
=====================================
libraries/base/Data/Foldable.hs
=====================================
@@ -507,7 +507,8 @@ class Foldable t where
-- @since 4.8.0.0
maximum :: forall a . Ord a => t a -> a
maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") .
- getMax . foldMap (Max #. (Just :: a -> Maybe a))
+ getMax . foldMap' (Max #. (Just :: a -> Maybe a))
+ {-# INLINEABLE maximum #-}
-- | The least element of a non-empty structure.
--
@@ -529,7 +530,8 @@ class Foldable t where
-- @since 4.8.0.0
minimum :: forall a . Ord a => t a -> a
minimum = fromMaybe (errorWithoutStackTrace "minimum: empty structure") .
- getMin . foldMap (Min #. (Just :: a -> Maybe a))
+ getMin . foldMap' (Min #. (Just :: a -> Maybe a))
+ {-# INLINEABLE minimum #-}
-- | The 'sum' function computes the sum of the numbers of a structure.
--
@@ -554,7 +556,8 @@ class Foldable t where
--
-- @since 4.8.0.0
sum :: Num a => t a -> a
- sum = getSum #. foldMap Sum
+ sum = getSum #. foldMap' Sum
+ {-# INLINEABLE sum #-}
-- | The 'product' function computes the product of the numbers of a
-- structure.
@@ -580,7 +583,8 @@ class Foldable t where
--
-- @since 4.8.0.0
product :: Num a => t a -> a
- product = getProduct #. foldMap Product
+ product = getProduct #. foldMap' Product
+ {-# INLINEABLE product #-}
-- instances for Prelude types
@@ -1111,10 +1115,15 @@ all p = getAll #. foldMap (All #. p)
-- See Note [maximumBy/minimumBy space usage]
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
-maximumBy cmp = foldl1 max'
- where max' x y = case cmp x y of
- GT -> x
- _ -> y
+maximumBy cmp = fromMaybe (errorWithoutStackTrace "maximumBy: empty structure")
+ . foldl' max' Nothing
+ where
+ max' mx y = Just $! case mx of
+ Nothing -> y
+ Just x -> case cmp x y of
+ GT -> x
+ _ -> y
+{-# INLINEABLE maximumBy #-}
-- | The least element of a non-empty structure with respect to the
-- given comparison function.
@@ -1128,10 +1137,15 @@ maximumBy cmp = foldl1 max'
-- See Note [maximumBy/minimumBy space usage]
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
-minimumBy cmp = foldl1 min'
- where min' x y = case cmp x y of
- GT -> y
- _ -> x
+minimumBy cmp = fromMaybe (errorWithoutStackTrace "minimumBy: empty structure")
+ . foldl' min' Nothing
+ where
+ min' mx y = Just $! case mx of
+ Nothing -> y
+ Just x -> case cmp x y of
+ GT -> y
+ _ -> x
+{-# INLINEABLE minimumBy #-}
-- | 'notElem' is the negation of 'elem'.
--
@@ -1268,12 +1282,6 @@ proportional to the size of the data structure. For the common case of lists,
this could be particularly bad (see #10830).
For the common case of lists, switching the implementations of maximumBy and
-minimumBy to foldl1 solves the issue, as GHC's strictness analysis can then
-make these functions only use O(1) stack space. It is perhaps not the optimal
-way to fix this problem, as there are other conceivable data structures
-(besides lists) which might benefit from specialized implementations for
-maximumBy and minimumBy (see
-https://gitlab.haskell.org/ghc/ghc/issues/10830#note_129843 for a further
-discussion). But using foldl1 is at least always better than using foldr1, so
-GHC has chosen to adopt that approach for now.
+minimumBy to foldl1 solves the issue, assuming GHC's strictness analysis can then
+make these functions only use O(1) stack space. As of base 4.16, we have switched to employing foldl' over foldl1, not relying on GHC's optimiser. See https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context.
-}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0f8a4655e39bed1ca39820abdd3df9db5706b036...6af074cecdee533791943af1191541f82abc34c4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0f8a4655e39bed1ca39820abdd3df9db5706b036...6af074cecdee533791943af1191541f82abc34c4
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20201130/8a817d20/attachment-0001.html>
More information about the ghc-commits
mailing list