[GHC] #9339: last is not a good consumer
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- The profiler indicates that `print $ last [(1::Int)..10^7]` (compiled with -O2) allocates around 8*10^8 bytes. Using the Henning Thienemann-inspired {{{ myLast = fromJust . foldr (\x -> Just . maybe x id) Nothing }}} (based on his code for viewR/unsnoc) reduces allocation by about half at the cost of some extra work. What we really want, I believe, is for `last` to fuse with the producer in a fashion that allows the Ints to be unboxed, eliminating all the allocation. I have no idea if this will fall out of the general fusion work planned for 7.9. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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): What general fusion work are you referring to? I only know about the improvements for fusing foldl, which doesn’t seem to apply here. Although maybe it could. How about this definition: {{{ myLast2 :: [a] -> a myLast2 = foldl (\_ x -> x) undefined }}} While `last` yields 800051648 bytes, and `myLast` yields 560084432 bytes, this runs in 51648 bytes (i.e. it fuses completely). Admitted, the resulting code looks almost stupidly efficient (at least if I write `10^7` as `10000` – I’m unjustifiably surprised that that is not constant-folded): {{{ Rec { $wgo $wgo = \ w_s3Aj -> case w_s3Aj of wild_Xf { __DEFAULT -> $wgo (+# wild_Xf 1); 10000000 -> 10000000 } end Rec } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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): Replying to [comment:1 nomeata]:
What general fusion work are you referring to? I only know about the improvements for fusing foldl, which doesn’t seem to apply here.
I was under the impression (possibly bogus) that the `foldl` fix involved some new transformation that could have other effects.
Although maybe it could. How about this definition:
{{{ myLast2 :: [a] -> a myLast2 = foldl (\_ x -> x) undefined }}}
While `last` yields 800051648 bytes, and `myLast` yields 560084432 bytes, this runs in 51648 bytes (i.e. it fuses completely).
That looks wonderful. Is it certain to be changed to a `foldl'` in cases where it ''doesn't'' fuse?
Admitted, the resulting code looks almost stupidly efficient (at least if I write `10^7` as `10000` – I’m unjustifiably surprised that that is not constant-folded):
Imagine the confusion if it were! Yes, `map f [m..n] !! p` ''could'' be optimized to O(1) whenever `m` has a known-sane type, but then all the newbies and half the oldies would get mixed up when little changes had radical performance impacts. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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):
That looks wonderful. Is it certain to be changed to a foldl' in cases where it doesn't fuse?
Hopefully not. `foldl'` would force the accumulator, which we do *not* want here (otherwise the `undefined` would be forced, or `last [undefined, 1]` would not work). I didn’t do further testing with that idea, it just crossed my mind. It maybe the that this implementation is only good when fusing works – would you mind trying to find out? In that case one would have to do the `replace, try to fuse, replace back` trick (which might be tricky with `foldl` itself getting inlined). Or maybe it is possible to use `foldl` and wrap the argument in a `Id`, so that forcing does the right thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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): Replying to [comment:3 nomeata]:
That looks wonderful. Is it certain to be changed to a foldl' in cases where it doesn't fuse?
Hopefully not. `foldl'` would force the accumulator, which we do *not* want here (otherwise the `undefined` would be forced, or `last [undefined, 1]` would not work).
Yes, you're right. I got mixed up a bit.
I didn’t do further testing with that idea, it just crossed my mind. It maybe the that this implementation is only good when fusing works – would you mind trying to find out?
I don't have anything beyond 7.8.3, and on 7.8.3 your code doesn't fuse. Could you maybe try it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- 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): Still not a full evaluation, but some more factoids: With {{{ myLast2 = foldl (\_ x -> x) undefined }}} I get {{{ myLast2 :: forall a. [a] -> a myLast2 = \ (@ a) -> foldl (myLast1) (undefined) }}} while when used (in the same model, non-fusing), this gets turned into the nice {{{ Rec { main_go :: [Int] -> Int -> Int main_go = \ (ds :: [Int]) (eta :: Int) -> case ds of _ { [] -> eta; : y ys -> main_go ys y } end Rec } }}} Writing {{{ myLast2 = inline foldl (\_ x -> x) undefined }}} also gives {{{ Rec { myLast1 :: forall a. [a] -> a -> a myLast1 = \ (@ a) (ds :: [a]) (eta :: a) -> case ds of _ { [] -> eta; : y ys -> myLast1 ys y } end Rec } myLast2 :: forall a. [a] -> a myLast2 = \ (@ a) (xs :: [a]) -> myLast1 xs (undefined) }}} So it looks good even when not fused. (Measurements are yet pending.) for the exported module, but when used, it produce -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer
-------------------------------------+-------------------------------------
              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):
 Ok, let’s do this systematically.
 My benchmarks: One possibly fusing invocation of `last`:
 {{{
 main = print $ Last.last $ filter odd $ [1::Int ..100000000]
 }}}
 and one non-fusing
 {{{
 f = id
 {-# NOINLINE f #-}
 main = print $ Last.last $ f $ filter odd $ [1::Int ..100000000]
 }}}
 I am comparing the existing implementation of `last`, which is
 {{{
 last []                 =  errorEmptyList "last"
 last (x:xs)             =  last' x xs
   where last' y []     = y
         last' _ (y:ys) = last' y ys
 }}}
 with the simpler
 {{{
 last = foldl (\_ x -> x) (errorEmptyList "last")
 }}}
 Just for fun (and because GHC HEAD still compiles), here the numbers with
 GHC-7.6:
 {{{
 LastTestFusing.hs
 <
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: patch 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: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch Comment: I wanted to push this as a phabricator review, but `arc` is currently broken for me. Hence I’ll parked it at `wip/T9339`. Marking as “patch” so that this is not forgotten. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: D86 | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Changes (by nomeata): * differential: => D86 Comment: Code for review at https://phabricator.haskell.org/D86 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Operating System: Unknown/Multiple Differential Revisions: Phab:D86 | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Changes (by nomeata): * differential: D86 => Phab:D86 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9339: last is not a good consumer
-------------------------------------+-------------------------------------
              Reporter:  dfeuer      |             Owner:
                  Type:  bug         |            Status:  patch
              Priority:  normal      |         Milestone:
             Component:              |           Version:  7.8.3
  libraries/base                     |          Keywords:
            Resolution:              |  Operating System:  Unknown/Multiple
Differential Revisions:  Phab:D86    |   Type of failure:  Runtime
          Architecture:              |  performance bug
  Unknown/Multiple                   |         Test Case:
            Difficulty:  Unknown     |          Blocking:
            Blocked By:              |
       Related Tickets:              |
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner 
 
            #9339: last is not a good consumer -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: fixed | Operating System: Unknown/Multiple Differential Revisions: Phab:D86 | Type of failure: Runtime Architecture: | performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9339#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
- 
                 GHC GHC