I just remembered an old idea I put to the GHC user's list here, and thought I should present it here.
As I understand it GHC inlines inlines only after a function is fully applied with respect to the syntactic left-hand side, so in order to control inlining and sharing, we sometimes see strange things like:
{-# INLINE foo #-}foo :: a -> b -> cfoo a = \b -> ...
It would be nice to be able to define the function syntactically in the way that's the most clear (e.g. in pointfree style, etc.) and specify at what point to inline something like this:
foo :: a -> {-# INLINE #-} b -> cfoo a b = ...-- or:foo = ...
..which tells the compiler to inline after applying the arguments to the left of the pragma, and GHC would do whatever trivial (I assume?) eta-conversion was required.
Trac metadata
Trac field
Value
Version
7.6.3
Type
FeatureRequest
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
I know; the current story for inlining is a compromise. If people really want the expressiveness, I'd prefer to do so by changing the existing INLINE pragma. Something like
{-# INLINE f (arity 2) #-}
or
{-# INLINE (f _ _) #-}
I don't see this as very high priority, but (everyone) please chime in if you care.
This would make a big difference in the readability of the lens code. We have an opn issue to move more of our arguments to the right of the = to get more agressive inlining, but it makes a few hundred functions harder to read.
Thanks. Can I encourage the other cc folks to say what their use-case is, as Edward has done? A plain "cc" says "I'm interested", but doesn't directly support the claim that it's an important or useful feature.
PS: Edward, could you offer a couple of concrete examples?
In that you can read (#.) as if it were (.), but if we switch it to
over l = \f -> runIdentity #. l (Identity #. f)
then GHC can inline it better in a call like
foo :: (a -> b) -> [a] -> [b]foo = over mapped
For reference:
mapped f = Identity #. fmap (runIdentity #. f)
Unfortunately, this means that the 'f' argument isn't in scope for where clauses, etc. which makes a lot of function implementations a lot uglier when they have more structure than this trivial example.
scanr1Of l f = snd . mapAccumROf l step Nothing where step Nothing a = (Just a, a) step (Just s) a = let r = f a s in (Just r, r)
There because f is referenced in the where clause step becomes explicitly parameterized on f, so we wind up having to either plumb the f argument in to step or we have to define step inside of a let clause inside of the lambda that takes f cluttering things up considerably.
Almost any combinator with a name that ends in "Of" which currently takes more than one argument on the left hand side of the equal sign is a candidate. Our current plan is to just bite the bullet and move all the code around to get better inlining, because we've found it makes an difference in quality of the resulting core.
My initial proposed syntax was supposed to be like {-# UNPACK #-} where the pragma applies to the thing to the right. Some folks on reddit thought it looked "weird" having it in the type signature.
Someone else mentioned that the {-# INLINE (f _ _) #-} syntax would be ambiguous in cases like {-# INLINE (f) #-} as to whether that meant the old behavior or "inline completely un-applied".
Maybe something like could also work: {-# INLINE f :: * -> * -> * #-} ?
Can I encourage the other cc folks to say what their use-case is
I have a number of templatic combinators for capturing common control structures. Arguments to these combinators can be divided into (a) parameters, (b) variables. That is, we often want to partially apply all the parameter arguments and then save the resulting function in order to call it repeatedly on different arguments. Because these combinators are templates, the parameters are often lambdas or data other literals, thus inlining the parameter-saturated version often gives a big boost in performance since the optimizer can crunch on those literals to produce some nice specialized code. This is essentially similar to the worker/wrapper transform.
There's a whole class of these where I also manually perform partial evaluation on the parameter-saturated version. For these combinators, the current setup doesn't matter, since we have a bunch of let-bindings between the abstractions for the parameters and the abstractions for the variables. However, there are other cases where I'm not doing that and it looks silly to write foo x y z = \a b c ->...
After trying a simple test, I noticed some strange performance results from stylistic changes to the code.
For example,
importqualifiedData.Vector.UnboxedasU{-# INLINE f #-}f::U.VectorInt->U.VectorInt->U.VectorIntf=U.zipWith(+)-- version 1--f x = U.zipWith (+) x -- version 2--f x = (U.zipWith (+) x) . id -- version 3--f x y = U.zipWith (+) x y -- version 4main=doletiters=100dim=221184y=U.replicatedim0::U.VectorIntletans=iterate(fy)y!!itersputStr$(show$U.foldl1'(+)ans)
Versions 1 and 2 of f run in 1.6 seconds, while versions 3 and 4 run in 0.09 seconds (with vector-0.10.9.1 and GHC 7.6.2, compiling with -O2).
According to an answer on the Vector trac (link below), this problem is because GHC only inlines on saturated function applications. Is there any way to expand the cases when GHC inlines to avoid having coding style affect performance?