[commit: ghc] master: Make sure GHC.List.last is memory-efficient (524ddbd)

git at git.haskell.org git at git.haskell.org
Fri Apr 24 09:15:08 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/524ddbdad5816f77b7b719cac0671eebd3473616/ghc

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

commit 524ddbdad5816f77b7b719cac0671eebd3473616
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Thu Apr 16 14:49:23 2015 +0200

    Make sure GHC.List.last is memory-efficient
    
    by eta-expanding its definition so that GHC optmizes the foldl here.
    Also make sure that other uses of last go via foldl as well, to allow
    list fusion (tested in T9339). Fixes #10260.


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

524ddbdad5816f77b7b719cac0671eebd3473616
 libraries/base/GHC/List.hs | 11 +++++++++--
 1 file changed, 9 insertions(+), 2 deletions(-)

diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index a712f9e..fcc89d3 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -84,8 +84,15 @@ last [x]                =  x
 last (_:xs)             =  last xs
 last []                 =  errorEmptyList "last"
 #else
--- use foldl to allow fusion
-last = foldl (\_ x -> x) (errorEmptyList "last")
+-- Use foldl to make last a good consumer.
+-- This will compile to good code for the actual GHC.List.last.
+-- (At least as long it is eta-expaned, otherwise it does not, #10260.)
+last xs = foldl (\_ x -> x) lastError xs
+{-# INLINE last #-}
+-- The inline pragma is required to make GHC remember the implementation via
+-- foldl.
+lastError :: a
+lastError = errorEmptyList "last"
 #endif
 
 -- | Return all the elements of a list except the last one.



More information about the ghc-commits mailing list