[commit: ghc] master: Fix space leak in sortBy (3d3975f)

git at git.haskell.org git at git.haskell.org
Tue Apr 18 00:35:32 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3d3975f2f4caf3af76a7ea27d2882ddaee7db3c9/ghc

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

commit 3d3975f2f4caf3af76a7ea27d2882ddaee7db3c9
Author: Gregory <greg7mdp at gmail.com>
Date:   Mon Apr 17 11:24:31 2017 -0400

    Fix space leak in sortBy
    
    This makes yields a small improvement in sort performance: around 3.5% in
    runtime on random Ints.
    
    Reviewers: austin, hvr, mpickering
    
    Subscribers: siddhanathan, rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3454


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

3d3975f2f4caf3af76a7ea27d2882ddaee7db3c9
 libraries/base/Data/OldList.hs | 9 ++++++---
 1 file changed, 6 insertions(+), 3 deletions(-)

diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index 428d3bd..ec937e7 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, MagicHash #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables,
+             MagicHash, BangPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -854,12 +855,14 @@ sortBy cmp = mergeAll . sequences
 
     ascending a as (b:bs)
       | a `cmp` b /= GT = ascending b (\ys -> as (a:ys)) bs
-    ascending a as bs   = as [a]: sequences bs
+    ascending a as bs   = let !x = as [a]
+                          in x : sequences bs
 
     mergeAll [x] = x
     mergeAll xs  = mergeAll (mergePairs xs)
 
-    mergePairs (a:b:xs) = merge a b: mergePairs xs
+    mergePairs (a:b:xs) = let !x = merge a b
+                          in x : mergePairs xs
     mergePairs xs       = xs
 
     merge as@(a:as') bs@(b:bs')



More information about the ghc-commits mailing list