[GHC] #9344: takeWhile does not participate in list fusion

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.3 Keywords: | Differential Revisions: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------- `takeWhile` doesn't do the list fusion thing. This alternative definition seems to fix that, at least to a great extent. It fused completely in a simple test, and incompletely but still usefully in a more complex one. I don't know how to write the appropriate translate/untranslate RULES for it yet. {{{ #!haskell {-# LANGUAGE ScopedTypeVariables #-} takeWhileFB :: forall a . (a -> Bool) -> [a] -> [a] takeWhileFB p xs = build tw' where tw' :: forall b . (a -> b -> b) -> b -> b tw' kons knil = foldr go knil xs where go x rest | p x = x `kons` rest | otherwise = knil }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Comment (by nomeata): I have some idea to make the translate/untranslate dance generic (and thus reliably usable by people wanting list fusion for their own functions) but I’ll ponder it some more. Can you explain why it fails in complex cases? And how does it perform? Is a fused `takeWhile (<10) [1..10000000]` slower than a non-fused? What happens with `takeWhile (<10) (cycle [1,100])` (if `cycle` fuses at all). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Comment (by dfeuer): I wouldn't call it "failing" so much as "incomplete success". I haven't investigated in detail, and may not be good enough with Core to figure it out anyway. The simple example {{{ #!haskell print $ length $ takeWhileFB (<10000000) [1..20000000] }}} allocates virtually nothing. The more complex example {{{ #!haskell print $ length $ filter (\x->x `rem` 3 == 0) $ takeWhileFB (<10000000) $ filter even [1..20000000] }}} allocates a substantial amount, but only something like a third of what `Prelude.takeWhile` does. I haven't attempted any benchmarking, and I'm too tired right now to look into those test cases. As for speed, if I'm not very much mistaken it takes a lot of slowness and/or a good number of mispredicted branches to make up for the cache effects that excessive allocation will have when combined with non-trivial code, so I believe that should probably be a secondary concern. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Comment (by nomeata):
As for speed, if I'm not very much mistaken it takes a lot of slowness and/or a good number of mispredicted branches to make up for the cache effects that excessive allocation will have when combined with non-trivial code, so I believe that should probably be a secondary concern.
True, and I’m not worried about that; I’m worried about the short- circuting of `takeWhile`: Does it properly stop the producer from calculating the rest of the list or not. From looking at the code I believe it does, though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I have some idea to make the translate/untranslate dance generic (and
#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Comment (by nomeata): thus reliably usable by people wanting list fusion for their own functions) but I’ll ponder it some more. I have pondered them some more, but they didn’t work out so far. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Runtime | Related Tickets: performance bug | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): I messed around with RULES a bit, and the following seem to work okay for starters. Some more rules will be needed to make map/takeWhile and takeWhile/map and whatever else do the right thing. One thing I'm not too clear about: what's the advantage of the explicitly recursive default definition over `takeWhile p = foldr (\x r -> if p x then x:r else []) []`? {{{ {-# INLINE [0] takeWhileFB #-} takeWhileFB :: (elt -> lst -> lst) -> lst -> (elt -> Bool) -> elt -> lst -> lst takeWhileFB kons knil p = \x rest -> if p x then x `kons` rest else knil {-# NOINLINE [1] takeWhile #-} takeWhile :: (a -> Bool) -> [a] -> [a] takeWhile _ [] = [] takeWhile p (x:xs) | p x = x : takeWhile p xs | otherwise = [] {-# RULES "takeWhile" [~1] forall p xs. takeWhile p xs = build (\kons knil -> foldr (takeWhileFB kons knil p) knil xs) "takeWhileList" [1] forall p. foldr (takeWhileFB (:) [] p) [] = takeWhile p "takeWhileFB" forall kons knil p q. takeWhileFB (takeWhileFB kons knil p) knil q = \x rest -> if (q x && p x) then x `kons` rest else knil #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Runtime | Related Tickets: performance bug | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nomeata):
One thing I'm not too clear about: what's the advantage of the explicitly recursive default definition over takeWhile p = foldr (\x r -> if p x then x:r else []) []
Nothing per se, unless benchmarking shows that the explicit version is faster, I guess. It might even be that simply {{{ takeWhile p xs = build (\kons knil -> foldr (takeWhileFB kons knil p) knil xs) {-# INLINEABLE takeWhile #-} }}} is good enough, assuming the non-inlined `takeWhile` gets compiled to good code (i.e. `build`, `foldr` and `takeWhileFB` are inlined). But I don’t have much experiences to predict that, so you’ll have to experiment and look at core to find out -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: duplicate | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Runtime | Related Tickets: #9132 performance bug | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => closed * resolution: => duplicate * related: => #9132 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC