[GHC] #9355: scanr does not participate in stream fusion

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: libraries/base | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Moderate (less | Type of failure: Runtime than a day) | performance bug Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- This should be a no-brainer—it's trivial two write `scanr` as a foldr, making it a good consumer. Wrapping it up in `build` makes it a good producer too, but may require back-and-forth RULES. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): OK, so it didn't turn out to be quite as trivial as I thought, but it looks like this does the trick: {{{#!haskell scanr :: forall a b . (a -> b -> b) -> b -> [a] -> [b] scanr f q0 ls = build scr where scr :: forall c . (b -> c -> c) -> c -> c scr c n = snd $ foldr go (q0, q0 `c` n) ls where go x (r,est) = let fxr = f x r in (fxr, fxr `c` est) }}} Fortunately, the tuples get unboxed as they should. Some extra rules may be needed for map, et al. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nomeata):
(because the argument to build isn't allowed to inspect its own result as the implementation in Data.List does),
I wouldn’t be surprised that returning `(# x, x:xs #)` is faster than returning `x:xs` and pattern matching on it. OTOH, the CPR optimization should change the code returning `x:xs` into (# x, xs #) and move the consing to the caller. Can’t you do that by hand, i.e.: {{{ scanrB :: forall a b . (a -> b -> b) -> b -> [a] -> [b] scanrB f q0 ls = build scr where scr :: forall c . (b -> c -> c) -> c -> c scr c n = case foldr go (q0, n) ls of (r, esult) -> c r esult where go x (r,est) = (f x r, r `c` est) }}} The Core looks a bit nicer: {{{ Scanr.scanrA :: forall a b. (a -> b -> b) -> b -> [a] -> [b] Scanr.scanrA = \ (@ a) (@ b) (f :: a -> b -> b) (q0 :: b) (ls :: [a]) -> let { a :: [b] a = GHC.Types.: q0 (GHC.Types.[]) } in letrec { $wgo :: [a] -> (# b, [b] #) $wgo = \ (w :: [a]) -> case w of _ { [] -> (# q0, a #); : y ys -> case $wgo ys of _ { (# ww1, ww2 #) -> let { fxr :: b fxr = f y ww1 } in (# fxr, GHC.Types.: fxr ww2 #) } }; } in case $wgo ls of _ { (# _, ww2 #) -> ww2 } Scanr.scanrB :: forall a b. (a -> b -> b) -> b -> [a] -> [b] Scanr.scanrB = \ (@ a) (@ b) (f :: a -> b -> b) (q0 :: b) (ls :: [a]) -> letrec { $wgo :: [a] -> (# b, [b] #) $wgo = \ (w :: [a]) -> case w of _ { [] -> (# q0, GHC.Types.[] #); : y ys -> case $wgo ys of _ { (# ww1, ww2 #) -> (# f y ww1, GHC.Types.: ww1 ww2 #) } }; } in case $wgo ls of _ { (# ww1, ww2 #) -> GHC.Types.: ww1 ww2 } }}} But I don’t expect there to be a measurable difference (and I didn’t check):
Some extra rules may be needed for map, et al.
not sure what you mean by that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:2 nomeata]:
(because the argument to build isn't allowed to inspect its own result as the implementation in Data.List does),
I wouldn’t be surprised that returning `(# x, x:xs #)` is faster than returning `x:xs` and pattern matching on it. OTOH, the CPR optimization should change the code returning `x:xs` into (# x, xs #) and move the consing to the caller.
Can’t you do that by hand, i.e.:
{{{ scanrB :: forall a b . (a -> b -> b) -> b -> [a] -> [b] scanrB f q0 ls = build scr where scr :: forall c . (b -> c -> c) -> c -> c scr c n = case foldr go (q0, n) ls of (r, esult) -> c r esult where go x (r,est) = (f x r, r `c` est) }}}
The Core looks a bit nicer:
{{{ Scanr.scanrA :: forall a b. (a -> b -> b) -> b -> [a] -> [b] Scanr.scanrA = \ (@ a) (@ b) (f :: a -> b -> b) (q0 :: b) (ls :: [a]) -> let { a :: [b] a = GHC.Types.: q0 (GHC.Types.[]) } in letrec { $wgo :: [a] -> (# b, [b] #) $wgo = \ (w :: [a]) -> case w of _ { [] -> (# q0, a #); : y ys -> case $wgo ys of _ { (# ww1, ww2 #) -> let { fxr :: b fxr = f y ww1 } in (# fxr, GHC.Types.: fxr ww2 #) } }; } in case $wgo ls of _ { (# _, ww2 #) -> ww2 }
Scanr.scanrB :: forall a b. (a -> b -> b) -> b -> [a] -> [b] Scanr.scanrB = \ (@ a) (@ b) (f :: a -> b -> b) (q0 :: b) (ls :: [a]) -> letrec { $wgo :: [a] -> (# b, [b] #) $wgo = \ (w :: [a]) -> case w of _ { [] -> (# q0, GHC.Types.[] #); : y ys -> case $wgo ys of _ { (# ww1, ww2 #) -> (# f y ww1, GHC.Types.: ww1 ww2 #) } }; } in case $wgo ls of _ { (# ww1, ww2 #) -> GHC.Types.: ww1 ww2 } }}}
But I don’t expect there to be a measurable difference (and I didn’t check):
Some extra rules may be needed for map, et al.
not sure what you mean by that?
Sorry, I've been a tad confused, as usual. The problem, I now see, is the bunch of thunks we produce. I don't think it's possible to make `scanr` a good producer, and I'm not even sure we can make it a significantly better one (though I'd have to profile to be sure). What we ''can'' do, in an apparently incompatible fashion, is make it a good consumer. Start with the current tail-eating implementation: {{{#!hs scanr _ q0 [] = [q0] scanr f qo (x:xs) = f x q : qs where qs@(q:_) = scanr f q0 xs }}} Rewriting that pattern match thing more explicitly: {{{#!hs scanr f q0 (x:xs) = let qs = scanr f q0 xs in f x (head qs) : qs }}} This, then is a plain old fold: {{{#!hs scanr f q0 = foldr go [q0] xs where go x qs = f x (head qs) : qs }}} If we apply it to a `build`, we get {{{#!hs scanr f q0 (build g) = g go [q0] where go x qs = f x (head qs):qs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Since `foldr` is strict in its list argument, I think it's then safe to go back to the pattern match style: {{{#!hs scanr f q0 = foldr go [q0] xs where go x qs@(q:_) = f x q : qs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:2 nomeata]:
(because the argument to build isn't allowed to inspect its own result as the implementation in Data.List does),
I wouldn’t be surprised that returning `(# x, x:xs #)` is faster than returning `x:xs` and pattern matching on it. OTOH, the CPR optimization should change the code returning `x:xs` into (# x, xs #) and move the consing to the caller.
Can’t you do that by hand, i.e.: SNIP But I don’t expect there to be a measurable difference (and I didn’t check):
I brilliantly read your code wrong and drew a bad conclusion. This looks much better than I initially thought (Look, ma, no `let`! ). I'm going to see how nofib likes it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => patch Comment: Unfortunately, `nofib` doesn't use `scanr` at all (and maybe nobody else does either). That said, the core looks very good in some small fusion tests. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 7.8.4
Component: | Version: 7.8.3
libraries/base | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Moderate (less
Unknown/Multiple | than a day)
Type of failure: Runtime | Blocked By:
performance bug | Related Tickets:
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.4 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9355: scanr does not participate in stream fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: Runtime | Blocked By: performance bug | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * milestone: 7.8.4 => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9355#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC