Skip to content
Snippets Groups Projects
Commit 3f3ac1cb authored by Joachim Breitner's avatar Joachim Breitner Committed by Ben Gamari
Browse files

Make Data.List.foldr1 inline

Previously, foldr1 would be defiend recursively and thus not inline.
This is bad, for example, when maximumBy has a strict comparison
function: Before the BBP, it was implemented via foldl1, which inlined
and yielded good code. With BBP, it goes via foldr1, so we better inline
this as well. Fixes #10830.

Differential Revision: https://phabricator.haskell.org/D1205
parent e9d65641
No related merge requests found
......@@ -355,9 +355,11 @@ match on everything past the :, which is just the tail of scanl.
-- and thus must be applied to non-empty lists.
foldr1 :: (a -> a -> a) -> [a] -> a
foldr1 _ [x] = x
foldr1 f (x:xs) = f x (foldr1 f xs)
foldr1 _ [] = errorEmptyList "foldr1"
foldr1 f = go
where go [x] = x
go (x:xs) = f x (go xs)
go [] = errorEmptyList "foldr1"
{-# INLINE [0] foldr1 #-}
-- | 'scanr' is the right-to-left dual of 'scanl'.
-- Note that
......
import GHC.OldList
main :: IO ()
main = maximumBy compare [1..10000] `seq` return ()
......@@ -69,3 +69,4 @@ test('T457', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run,
test('T9128', normal, compile_and_run, [''])
test('T9390', normal, compile_and_run, [''])
test('T10830', extra_run_opts('+RTS -K100k -RTS'), compile_and_run, [''])
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