New INLINE pragma syntax idea, and some questions

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


I've been wondering for some time about the details of how GHC uses
syntax with inlining, and how other transformations come into play in
the process (I recently asked a question on SO if anyone wants some
karma: http://stackoverflow.com/q/11690146/176841). I know this is a
big topic and there's probably a lot more out there I should read.

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.

An alternative if including the pragma in the type sig. isn't sound,
is to allow it in the function definition left-hand side, after the
bindings we would like applied before inlining.

Brandon



More information about the Glasgow-haskell-users mailing list