[GHC] #15426: `elemIndex` and `findIndex` still can't fuse

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: | Version: 8.4.3 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Ticket #14387 introduced a change to the implementation of `listToMaybe` to allow: {{{#!hs findIndex p = listToMaybe . findIndices p }}} to fuse. However, to take advantage of this, it looks like we also need `findIndex` (and `elemIndex`) to be marked inlinable (or some similar step). As a concrete example, the module: {{{#!hs module Foo where import Data.List (findIndex) foo :: Maybe Int foo = findIndex (==999999) [1..1000000] }}} compiled with GHC 8.4.3 using `-O2` produces the following unfused core: {{{#!hs foo_go = \ ds1_a2ws eta_a2wt -> case ds1_a2ws of { [] -> Nothing; : y_a2wx ys_a2wy -> case eqInteger# y_a2wx ds_r2we of { __DEFAULT -> foo_go ys_a2wy (+# eta_a2wt 1#); 1# -> Just (I# eta_a2wt) } } foo = foo_go (enumDeltaToInteger1 foo2 foo1) 0# }}} but if the definition of `findIndex` from `Data.OldList` is copied into the module or imported from another module with an `INLINABLE` pragma, then it fuses fine: {{{#!hs foo_go = \ x_a2Du eta_B1 -> case gtInteger# x_a2Du lim_r2Ey of { __DEFAULT -> case eqInteger# x_a2Du ds_r2Cv of { __DEFAULT -> foo_go (plusInteger x_a2Du foo1) (+# eta_B1 1#); 1# -> Just (I# eta_B1) }; 1# -> Nothing } foo = foo_go foo1 0# }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Looks plausible to me. Would anyone like to submit a patch and (preferably) a test that demonstrates fusion. Please include a Note with the INLINABLE pragma to explain carefully why it's there. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kabuhr): Okay, I'm working on a patch/test case, but I need some advice. The issue seems to be that because `findIndices` is marked `INLINE` instead of merely `INLINABLE`, the unfolding in the interface file for the function: {{{ #!haskell findIndex :: (a -> Bool) -> [a] -> Maybe Int findIndex p = listToMaybe . findIndices p }}} has already been turned into an unfusible version. I can fix this in one of two ways, either by marking `findIndex` as `INLINABLE` which puts a fusible version of `findIndex` (with `findIndices` already inlined) into the interface file **OR** by demoting `findIndices` from `INLINE` to merely `INLINABLE`. (It must be marked `INLINABLE` to keep a fusible version in the interface file; if it's unmarked, an unfusible unfolding is included instead.) I favor the second option, because it seems cleaner and also seems more likely to generate better code when `findIndices` is used directly in user code (i.e., because it will help avoid the same situation we currently have with `findIndex` and `elemIndex`). Is there any drawback to switching `findIndices` from `INLINE` to `INLINABLE`? In other words, what is the motivation in the first place for marking `findIndices` as `INLINE` instead of just `INLINABLE`. I've run the normal test suite (`make test`) before and after the change and didn't observe any performance regressions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kabuhr): After getting the side-by-side performance comparison stuff from wip/perf- testsuite running, I can confirm that changing `findIndices` from `INLINE` to `INLINABLE` causes no performance regressions in any of the performance tests. So, I'll try to put together a patch and submit to Phabricator. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Changes (by kabuhr): * owner: (none) => kabuhr * testcase: => testsuite/tests/perf/should_run/T15426.hs * differential: => https://phabricator.haskell.org/D5063 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Comment (by kabuhr): I also ran the nofib benchmark suite with and without the change (switching `findIndices` from `INLINE` to `INLINABLE`). The change resulted in a slight increase (3%) to memory usage for the `cacheprof` benchmark with no change to elapsed time, and a large decrease (41%) to memory usage for the `maillist` benchmark. There were no other memory usage differences. There were variations in elapsed time across the benchmark suite in both directions over the range -5.6% to +4.4, but these appear to be spurious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Comment (by simonpj):
The change resulted in a slight increase (3%) to memory usage for the cacheprof benchmark
By "memory usage" do you mean "allocation"? A 3% increase in allocation is very strange, and worth understanding better. (I use `-ticky` for these kind of before-and-after comparisons.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Comment (by kabuhr): No, these differences were for the "TotalMem" column from the "nofib- analyse" tool. I gather this corresponds to the memory "in use" in "-RTS +t" output, which is peak OS allocation and presumably sensitive to GC timing. After doing some more testing, it seems both the `cacheprof` and `maillist` differences are spurious (e.g., `maillist` either "uses" `8M` or `16M` during each run, and I just happened to have a string of good luck on the `INLINABLE` test). There were no differences in allocations for these or any of the other benchmarks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Comment (by simonpj): OK fine. So if I understand aright: * Nofib gets no better but no worse * More fusion happens in other cases (eg the Description) Sounds good to me. It would be good to include a perf regression test that will trip if fusion fails in the future. And a Note to explain the INLINABLE pragma. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Changes (by kabuhr): * status: new => patch Comment: Yes, that summary is correct. In the current Phab:D5063 that's pending review, I have added a performance regression test `T15426.hs`, and I have annotated the change in `OldList.hs` with: {{{ #!haskell -- (Note that making this INLINABLE instead of INLINE allows -- 'findIndex' to fuse, fixing #15426.) }}} assuming that's sufficient. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15426: `elemIndex` and `findIndex` still can't fuse
-------------------------------------+-------------------------------------
Reporter: kabuhr | Owner: kabuhr
Type: bug | Status: patch
Priority: normal | Milestone: 8.8.1
Component: libraries/base | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| testsuite/tests/perf/should_run/T15426.hs
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://phabricator.haskell.org/D5063
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15426: `elemIndex` and `findIndex` still can't fuse -------------------------------------+------------------------------------- Reporter: kabuhr | Owner: kabuhr Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: libraries/base | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/perf/should_run/T15426.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D5063 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15426#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC