Skip to content
Snippets Groups Projects
Commit 524ddbda authored by Joachim Breitner's avatar Joachim Breitner
Browse files

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.
parent a55bfabb
No related merge requests found
......@@ -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.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment