[commit: ghc] wip/D1229: Further simplify the story around minimum/maximum (c6b82e9)
git at git.haskell.org
git at git.haskell.org
Mon Sep 7 11:52:55 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/D1229
Link : http://ghc.haskell.org/trac/ghc/changeset/c6b82e99f41e03d4b101b3a32312defad711f56a/ghc
>---------------------------------------------------------------
commit c6b82e99f41e03d4b101b3a32312defad711f56a
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Sep 7 13:48:10 2015 +0200
Further simplify the story around minimum/maximum
After I have found out that I should look at -ddump-prep and not
-ddump-core, I noticed that these days, GHC is perfectly capeable of
turning (the equivalent) of foldl to (the equivalent) of foldl' if the
operation in question is strict. So instead of using rewrite rules to
rewrite maximum to a strictMaximum for certain types, we simply use
SPECIALIZE.
This also marks maximum/minimum as INLINEABLE, so that client code can
get similar specializations, hopefully even automatically. And inded,
minimum applied to [Double] produces good code (although due to
inlineing, not due to specialization, it seems).
I checked (by looking at the core) that this still fixes #10788.
Differential revision: https://phabricator.haskell.org/D1229
>---------------------------------------------------------------
c6b82e99f41e03d4b101b3a32312defad711f56a
libraries/base/GHC/List.hs | 34 +++++++++-------------------------
1 file changed, 9 insertions(+), 25 deletions(-)
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index 86ff868..bbaa0a2 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -400,43 +400,27 @@ scanr1 f (x:xs) = f x q : qs
-- It is a special case of 'Data.List.maximumBy', which allows the
-- programmer to supply their own comparison function.
maximum :: (Ord a) => [a] -> a
-{-# INLINE [1] maximum #-}
+{-# INLINEABLE maximum #-}
maximum [] = errorEmptyList "maximum"
maximum xs = foldl1 max xs
-{-# RULES
- "maximumInt" maximum = (strictMaximum :: [Int] -> Int);
- "maximumInteger" maximum = (strictMaximum :: [Integer] -> Integer)
- #-}
-
--- We can't make the overloaded version of maximum strict without
--- changing its semantics (max might not be strict), but we can for
--- the version specialised to 'Int'.
-strictMaximum :: (Ord a) => [a] -> a
-strictMaximum [] = errorEmptyList "maximum"
-strictMaximum xs = foldl1' max xs
-{-# SPECIALIZE strictMaximum :: [Int] -> Int #-}
-{-# SPECIALIZE strictMaximum :: [Integer] -> Integer #-}
+-- We want this to be specialized so that with a strict max function, GHC
+-- produces good code. Note that to see if this is happending, one has to
+-- look at -ddump-prep, not -ddump-core!
+{-# SPECIALIZE maximum :: [Int] -> Int #-}
+{-# SPECIALIZE maximum :: [Integer] -> Integer #-}
-- | 'minimum' returns the minimum value from a list,
-- which must be non-empty, finite, and of an ordered type.
-- It is a special case of 'Data.List.minimumBy', which allows the
-- programmer to supply their own comparison function.
minimum :: (Ord a) => [a] -> a
-{-# INLINE [1] minimum #-}
+{-# INLINEABLE minimum #-}
minimum [] = errorEmptyList "minimum"
minimum xs = foldl1 min xs
-{-# RULES
- "minimumInt" minimum = (strictMinimum :: [Int] -> Int);
- "minimumInteger" minimum = (strictMinimum :: [Integer] -> Integer)
- #-}
-
-strictMinimum :: (Ord a) => [a] -> a
-strictMinimum [] = errorEmptyList "minimum"
-strictMinimum xs = foldl1' min xs
-{-# SPECIALIZE strictMinimum :: [Int] -> Int #-}
-{-# SPECIALIZE strictMinimum :: [Integer] -> Integer #-}
+{-# SPECIALIZE minimum :: [Int] -> Int #-}
+{-# SPECIALIZE minimum :: [Integer] -> Integer #-}
-- | 'iterate' @f x@ returns an infinite list of repeated applications
More information about the ghc-commits
mailing list