[commit: packages/base] wip/T7994: Inline maximum/minium a bit more aggresively (5b68483)

git at git.haskell.org git at git.haskell.org
Wed Feb 5 23:57:30 UTC 2014


Repository : ssh://git@git.haskell.org/base

On branch  : wip/T7994
Link       : http://ghc.haskell.org/trac/ghc/changeset/5b68483804d9c03e72ae707791b34e96bc55b8d3/base

>---------------------------------------------------------------

commit 5b68483804d9c03e72ae707791b34e96bc55b8d3
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.


>---------------------------------------------------------------

5b68483804d9c03e72ae707791b34e96bc55b8d3
 Data/List.hs |    4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/Data/List.hs b/Data/List.hs
index 987ae17..06c752b 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