scryer-prolog icon indicating copy to clipboard operation
scryer-prolog copied to clipboard

Avoiding the overhead of meta-calls in maplist/N and foldl/N by partial evaluation

Open triska opened this issue 3 years ago • 12 comments

When the first argument of the frequently used meta-predicates maplist/N and foldl/N is known at compilation time (which is the most common case), then the overhead of the meta-call can be avoided by a goal expansion that replaces these goals by calls of auxiliary predicates that are generated at compilation time, one for each partial goal skeleton that occurs.

For example, let's take maplist/2 (the same holds mutatis mutandis for the other meta-predicates), which is defined as:

maplist(_, []).
maplist(Cont1, [E1|E1s]) :-
    call(Cont1, E1),
    maplist(Cont1, E1s).

Our goal is to avoid the use of call/2, and call the needed predicate directly instead of indirectly via a term on the heap. So, when for example the following goal occurs in a program as part of a predicate body:

...,
maplist(p, Ls),
...,

then we can change this to a goal that invokes an automatically generated auxiliary predicate that partially evaluates the definition of maplist/2 so that it is specialized for the specific invocation of p/1. Let's call this auxiliary predicate maplist_for_p/1, with the following definition:

maplist_for_p([]).
maplist_for_p([L|Ls]) :-
    p(L),
    maplist_for_p(Ls).

Note that p/1 is now called directly in this definition instead of indirectly via call/2, thus avoiding the overhead of the meta-call. With this definition available, the goal in the clause body can be changed (via goal_expansion/2) to:

...,
maplist_for_p(Ls),
...,

A clever way to implement this would use the existing goal and term expansion mechanisms and augment library(lists) to generate the needed auxiliary predicates in each module that uses maplist/N and foldl/N, for example by collecting the needed clauses and producing them by expanding end_of_file to the needed definitions.

triska avatar Jun 19 '22 19:06 triska

Partial evaluation telle quelle is quite a rabbit hole to fall into. What might be a way out is to take the meta_predicate declarations as (one) precondition for such an expansion. The approach SWI has taken here does not feel right at all.

UWN avatar Jun 20 '22 06:06 UWN

A further precondition: The (considered) meta arguments are used only in passing it further on to other meta arguments. No general unification takes place.

UWN avatar Jun 20 '22 07:06 UWN

Partial evaluation telle quelle is quite a rabbit hole to fall into. What might be a way out is to take the meta_predicate declarations as (one) precondition for such an expansion. The approach SWI has taken here does not feel right at all.

Yes, I've been thinking of it intensely over the past week. My current strategy is to complete a partial goal in a meta-predicate like maplist as follows. In

?- maplist(phrase(a ; b), Lss, Tss).

phrase(a;b) would be furnished with fresh supplementary variables phrase((a;b), A1, A2) (since maplist is a meta-predicate of type (2,?,?)). phrase((a;b), A1, A2) is submitted to expand_goal and the maplist would become

?- maplist('$call_inlined'(<pointer to fact below>), Lss, Tss).

where

<nameless fact pointed to by '$call_inlined'>(A1, A2) :- a(A1,A2);b(A1,A2).

Is this too aggressive? phrase(a;b) is expanded to its most general form by appending the fresh variables A1,A2 to its argument list.

mthom avatar Jun 29 '22 16:06 mthom

Is this too aggressive?

Do you already know the definition of maplist/3 by heart? (That is what I suspect), or is this rather a result of analyzing the maplist/3 definition from scratch? I would prefer the second approach but probably more than just meta-predicate declarations are needed. Like a 'typing' of such meta-arguments with variables named _2 etc. And as a consequence, maybe even type mismatches may result...

UWN avatar Jun 29 '22 18:06 UWN

It's just the result of considering the meta-predicate declaration.

mthom avatar Jun 29 '22 19:06 mthom

The outline Jan Weilemaker gives in the second post of this page https://discourse.swi-prolog.org/t/how-is-goal-expansion-for-closures-defined/3365 is exactly the idea I have in mind. But it appears (on StackOverflow for example) that people have some reservations about how goal expansion interacts with call/N in SWI. So, I'm hesitating.

mthom avatar Jun 30 '22 03:06 mthom

Maybe a fresher reconsideration is possible. By considering why goal expansion is necessary. And no, clpz is not a good example, as there it serves optimizations purposes only that are tantamount to a single unfold. These optimizations could be performed by other means as well and could even provide guarantees that goal expansion cannot.

UWN avatar Jun 30 '22 05:06 UWN

Could you please expand on this: Which other means do you have in mind?

I am asking also because clpz does a bit more than "a single unfold": For example, when we define:

p(X) :-
        X #

then this is expanded to:

p(A) :-
   (  integer(A) ->
      3>=A+1
   ;  B=3,
      clpz:clpz_geq(B,A+1)
   ).

So, it is not only a matter of "inlining" clpz:clpz_geq/2, but in a sense actually "expanding" a constraint to such a case-distinction.

triska avatar Jul 06 '22 18:07 triska

The effect of this expansion in p/1 is completely defined by the original, unexpanded program. Both behave exactly the same way modulo resource consumption (and, if p/1 is public (3.142), modulo clause/2). In fact, exactly that very expanded code could be present in the definition of (#<)/2. The definition of which is not easy to inspect with clause(clpz:clpz_geq_(X,Y),B). reads

... .
clpz_geq_(A,B) :-
   integer(A),
   C=A,
   nonvar(B),
   B=D+E,
   F=D,
   integer(E),
   G=E,
   true,
   !,
   H is C-G,
   clpz_geq_(H,F).
... .

which looks quite unfoldable.

To put it differently, are there any uses of goal expansion that go beyond just such optimizations?

UWN avatar Jul 06 '22 19:07 UWN

Let's suppose there are no cases that go beyond such optimizations: Which other means did you have in mind to implement these? Can p/1 be used as an example to illustrate these mechanisms?

triska avatar Jul 06 '22 20:07 triska

Let's suppose there are no cases ...

When we suppose that there are no cases for goal expansion other than optimization, goal expansion should never happen during call/N since a direct execution would be much faster. At least for a single goal. When the goal consists of several control constructs, things might be different.

But currently this expansion mechanism completely needlessly deteriorates execution, like in #1390 where local variables are unnecessarily globalized. The very purpose of the WAM is to have such an efficient way of distinguishing local and global variables. And with such cases, this advantage is nixed. (Efficient, because lastcall optimization works here smoothly in contrast to the ZIP and VAM).

For those other cases like p/1, goal expansion makes sense, but only by guaranteeing equivalence. That is, the program must behave the same with and without goal expansion. And if it does not, then that expansion is a problem. Things there might get a bit complex by accidental instantiation of expanded goals. (I have not tried current systems for this for a long time..)

UWN avatar Jul 08 '22 08:07 UWN

As far as I can tell, this is now completely addressed in the rebis-dev branch, with a truly impressive and general engine-based approach to inlining which requires no changes at all to any libraries and brings substantial performance improvements to maplist/N, foldl/N and other common meta-predicates, as well as in superficially quite unrelated cases such as #1506 and https://github.com/mthom/scryer-prolog/discussions/1513 which have already occurred in practice.

This is one of the most innovative and exciting developments so far in Scryer Prolog, and I think I can safely close this issue once rebis-dev is merged. Thank you a lot!

triska avatar Jul 23 '22 20:07 triska

This is now available in master, so I am closing this issue. Thank you a lot!

triska avatar Nov 10 '22 22:11 triska