Skip to content
Snippets Groups Projects
Commit 4e1dfc37 authored by David Feuer's avatar David Feuer Committed by Joachim Breitner
Browse files

Make scanr a good producer and consumer

This fixes #9355.
parent 488e95b4
No related merge requests found
......@@ -229,11 +229,29 @@ foldr1 _ [] = errorEmptyList "foldr1"
--
-- > head (scanr f z xs) == foldr f z xs.
{-# NOINLINE [1] scanr #-}
scanr :: (a -> b -> b) -> b -> [a] -> [b]
scanr _ q0 [] = [q0]
scanr f q0 (x:xs) = f x q : qs
where qs@(q:_) = scanr f q0 xs
{-# INLINE [0] strictUncurryScanr #-}
strictUncurryScanr :: (a -> b -> c) -> (a, b) -> c
strictUncurryScanr f pair = case pair of
(x, y) -> f x y
{-# INLINE [0] scanrFB #-}
scanrFB :: (a -> b -> b) -> (b -> c -> c) -> a -> (b, c) -> (b, c)
scanrFB f c = \x (r, est) -> (f x r, r `c` est)
{-# RULES
"scanr" [~1] forall f q0 ls . scanr f q0 ls =
build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls))
"scanrList" [1] forall f q0 ls .
strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) =
scanr f q0 ls
#-}
-- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
scanr1 :: (a -> a -> a) -> [a] -> [a]
......
......@@ -77,6 +77,8 @@
second argument, so that the fusion RULES for it do not change the
semantics. (#9596)
* `scanr` now takes part in list fusion (#9355)
## 4.7.0.1 *Jul 2014*
* Bundled with GHC 7.8.3
......
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