[GHC] #15426: `elemIndex` and `findIndex` still can't fuse
GHC
ghc-devs at haskell.org
Fri Jul 20 19:43:01 UTC 2018
#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
More information about the ghc-tickets
mailing list