New INLINE pragma syntax idea, and some questions

Brandon Simmons brandon.m.simmons at gmail.com
Sat Aug 4 15:53:41 CEST 2012


On Sat, Aug 4, 2012 at 6:22 AM, Dan Doel <dan.doel at gmail.com> wrote:
>
> On Aug 3, 2012 11:13 PM, "Brandon Simmons" <brandon.m.simmons at gmail.com>
> wrote:
>> In particular I don't fully understand why these sorts of contortions...
>>
>>
>> http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/GHC-List.html#foldl
>>
>> ...are required. It seems like a programmer has to throw "equational
>> reasoning", separation of concerns, and all the little elegant bits
>> about the language out the window just to indicate something boring to
>> the compiler.
>>
>> Disclaimer: The following is less a proposal meant to be taken
>> seriously, and more me trying to better understand things.
>>
>> Could the following be used as syntax for indicating inlining? Rather
>> than relying on the syntactic LHS, instead let that be specified in
>> the type signature...
>>
>>     foldl        :: (a -> b -> a) -> a -> [b] -> {-# INLINE #-} a
>>     foldl f z []     =  z
>>     foldl f z (x:xs) = foldl f (f z x) xs
>>
>> ...indicating, in this case, that foldl should be inlined when
>> "fully-applied" means its first three arguments (I guess that's the
>> intent of the original version linked above?). Then (waves hands) the
>> compiler could do the necessary transformations that the programmer
>> had to do to foldl above. Maybe what I'm proposing is actually a
>> separate NORECURSIVE_TRANSFORM pragma or something
>
> That's not quite the effect. What has been done to foldl there is known as
> the static argument transform. It avoids passing constant arguments along in
> recursion. f is the only static argument to foldl (foldr by contrast has
> two).

I think I didn't pick a very good example there. The only thing that
bothers me about this foldl is the presence of z0 xs0, which I think
are only there on the LHS to indicate to GHC where it should inline.

The "static argument transform" itself seems like just good
programming practice (don't repeat yourself, abstract out common
things), and the implications on optimized code make a lot of sense,
so I think that doesn't bother me.

>
> This can be important for multiple reasons. Sometimes it frees up registers.
> Here, we may inline foldl and possibly specialize the loop to a statically
> known f. That is often a big win. For instance, if you write sum with foldl,
> you can inline, do a worker wrapper transform, and work on unboxed integers
> with raw adds (probably) instead of going through multiple layers of
> indirection.
>
> There was some work on making GHC automatically SAT, but of it's a bit
> tricky with regard to when it's worth it, so I don't think it's been put in.
>
> I have code that relies on this sort of thing a lot, so if someone comes up
> with a good way to automate it, I wouldn't complain.
>
> Dan

Thanks for the details and clarifications!

Brandon



More information about the Glasgow-haskell-users mailing list