Loop unrolling + fusion ?

Claus Reinke claus.reinke at talk21.com
Fri Mar 6 17:26:49 EST 2009


> The implementation I'm thinking of is basically trivial. You just add
> the information gathered from the pragmas onto the Ids, then have a
> dedicated core pass that looks at the pragmas and does it's
> worker/wrapper thing. The technology to do peeling/unrolling is
> trivial and there already examples in the codebase (in case liberation
> and SAT). If someone can spec out what they actually want and GHC HQ
> give it the thumbs up I would be happy to do the grunt work on
> implementing this feature.

Yes, please!-)

My preferred spec would be roughly

{-# NOINLINE f #-}
    as now

{-# INLINE f #-} 
    works as now, which is for non-recursive f only (might in future
    be taken as go-ahead for analysis-based recursion unfolding)

{-# INLINE f PEEL n #-}
    inline calls *into* recursive f (called loop peeling for loops)
 
{-# INLINE f UNROLL m #-}
    inline recursive calls to f *inside* f (called loop unrolling for loops)

{-# INLINE f PEEL n UNROLL m #-}
    combine the previous two

    The numeric parameters are to be interpreted as if each call to
    f was annotated with both PEEL and UNROLL limits, to be
    decreased as appropriate for every PEEL or UNROLL action.
    Peeling and unrolling stop when the respective count annotation
    has reached 0. Note that mutual recursion is the domain of PEEL,
    while UNROLL only applies to direct recursion.

    {-# INLINE f PEEL n #-}, for n>0, corresponds to worker/
    wrapper transforms (previously done manually) + inline wrapper,
    and should therefore also be taken as a hint for the compiler to 
    try the static argument transformation for f (the "worker").

    Non-supporting implementations should treat these as INLINE
    pragmas (same warning/ignore or automatic unfold behaviour).

About the pragma name: as far as I can tell, Hugs simply ignores
INLINE pragmas, no matter what they say, other implementations
could just ignore the PEEL/UNROLL part (possibly with a warning)
- do any of them support INLINE on recursive definitions?

The only problem is that GHC itself fails with a parse error, which
would lead to version issues (perhaps GHC should have allowed
for additional information to otherwise syntactically complete pragmas,
or warnings instead of errors, but that hitch is out in the wild now).

Having separate PEEL/UNROLL pragmas would make ignoring
the default action, but would clutter the pragma name space as well
as the source code; it also wouldn't make explicit that we are indeed 
refining the INLINE pragma for the case of recursive functions (which 
GHC currently ignores or complains about), by detailing how we want 
the recursive definition to be inlined.

Since we are talking about a refinement of the INLINE pragma, we
also need to look at that pragma's existing subtleties:-(

- no functions inlined into f: should be subject to override by
    INLINE pragmas (even for the non-recursive case?)
- no float-in/float-out/cse: ??
- no worker/wrapper transform in strictness analyser: we do get the 
    same effect from INLINE PEEL, so this should be okay, right?
- loop breakers: PEEL/UNROLL have their own limits, creating
    an intrinsic loop breaker when the counters run out

Is that sufficient?
Claus



More information about the Glasgow-haskell-users mailing list