diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index 0ed8cafbd61fb4d532d03d65a805a19da9fdef77..1846121bdafe65ca265c5b71e5f70fa7ff05ca3b 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -385,29 +385,11 @@ foldr1 f = go -- Note that -- -- > 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 #-} -- See Note [Inline FB functions] -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 - #-} - -- | \(\mathcal{O}(n)\). 'scanr1' is a variant of 'scanr' that has no starting -- value argument. scanr1 :: (a -> a -> a) -> [a] -> [a] diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index d5694e7a39b5242964b2b3fa1443e5a9914a406d..7399f371d1309122d6acea0b5d95d694a78f1320 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -57,6 +57,8 @@ `Word`, and `WordN` now throw an overflow exception for negative shift values (instead of being undefined behaviour). + * `scanr` no longer participates in list fusion (due #16943) + ## 4.12.0.0 *21 September 2018* * Bundled with GHC 8.6.1