[commit: packages/base] wip/T7994: Inline maximum/minium a bit more aggresively (bfee447)
git at git.haskell.org
git at git.haskell.org
Wed Jan 29 17:33:21 UTC 2014
Repository : ssh://git@git.haskell.org/base
On branch : wip/T7994
Link : http://ghc.haskell.org/trac/ghc/changeset/bfee44776e3087c29f6a9dcd60ad2f5b1220d42c/base
>---------------------------------------------------------------
commit bfee44776e3087c29f6a9dcd60ad2f5b1220d42c
Author: Joachim Breitner <breitner at kit.edu>
Date: Wed Jan 29 17:29:53 2014 +0100
Inline maximum/minium a bit more aggresively
in order to allow fusion of the foldr in the foldl in the foldl' therein.
>---------------------------------------------------------------
bfee44776e3087c29f6a9dcd60ad2f5b1220d42c
Data/List.hs | 4 ++--
1 file changed, 2 insertions(+), 2 deletions(-)
diff --git a/Data/List.hs b/Data/List.hs
index 602a53f..d3c900c 100644
--- a/Data/List.hs
+++ b/Data/List.hs
@@ -519,7 +519,7 @@ insertBy cmp x ys@(y:ys')
-- It is a special case of 'Data.List.maximumBy', which allows the
-- programmer to supply their own comparison function.
maximum :: (Ord a) => [a] -> a
-{-# NOINLINE [1] maximum #-}
+{-# INLINE [1] maximum #-}
maximum [] = errorEmptyList "maximum"
maximum xs = foldl1 max xs
@@ -540,7 +540,7 @@ strictMaximum xs = foldl1' max xs
-- It is a special case of 'Data.List.minimumBy', which allows the
-- programmer to supply their own comparison function.
minimum :: (Ord a) => [a] -> a
-{-# NOINLINE [1] minimum #-}
+{-# INLINE [1] minimum #-}
minimum [] = errorEmptyList "minimum"
minimum xs = foldl1 min xs
More information about the ghc-commits
mailing list