New INLINE pragma syntax idea, and some questions

Dan Doel dan.doel at gmail.com
Sat Aug 4 12:22:45 CEST 2012


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).

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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20120804/4c922e47/attachment.htm>


More information about the Glasgow-haskell-users mailing list