How to get to a fixed point with goal expansion?

library(rdet) expands goal(X) to ( goal(X) -> true ; error(...) ), which would lead to infinite expansion unless goal(X) is marked as already expanded. The solution that library(rdet) uses is to output a “marker” predicate for each goal and not do the expansion if that “marker” already exists.

The problem is: how to mark a goal as opposed to a term?
prolog_load_context(term_position, Pos) gives the position of the enclosing term, and there doesn’t seem to be an equivalent call that gives the position of the current goal within the term.

Or is there another way to prevent going into an infinite loop on goal expansion?

(This problem is described at https://github.com/rla/rdet/issues/2)

1 Like

Good question. In theory you could use same_term/2 to locate the goal inside the term as provided by prolog_load_context(term, Term). That is all rather hacky though. The fact that the compiler toplevel is a failure driven loop could also be used to maintain a global variable to keep track of the terms processed. I doubt it is a good idea to forever commit to the failure driven approach though.

So, what else? I have some really early thoughts about wrapping at a low level. Not sure whether and how that will see daylight. I might need something like that to enhance the tabling implementation.

We could also rewrite expand_goal/2 to block expanding the same goal. So, if goal_expansion/2 succeeds for X, we go down into the expanded term but will not pass X to goal expansion again should we find it.

I had a look at the SICStus docs. That also suggests using a naive fixed point approach. Any systems that have a solution?

1 Like

I did a quick hack to rdet (see my followup at https://github.com/rla/rdet/issues/2), which seems to mostly fix the problem. Basically, where rdet used the info from prolog_load_context(term_position, ...), I added the goal term. This works as long as the identical goal (with the identical variables) appears more than once in a term’s goals.

This is an interesting problem and one that I dedicated some time in the past. In Logtalk, I had for quite some time a partial solution but with some limitations that always prevented me from advertising it. The workaround in the rdet pack, with or without Peter’s fix, is too fragile and hacky. I don’t think anyone, including the original author, is comfortable with it. A better solution could be to allow marking a goal to not be further expanded. Noting that the @ mode indicator is used for arguments that are not modified by a call, how about reusing it as a marker? In this particular case, we would simply write:

goal_expansion(Goal, ExpandedGoal) :-
	...,
	ExpandedGoal = (@Goal -> true; throw(error(goal_failed(Goal, ...)))).

I have prototyped this solution easily in the Logtalk compiler. It works nicely (fixing the issue Peter described at https://github.com/rla/rdet/issues/2). Jan, how easily could this solution be implemented in SWI-Prolog?

I like the @ solution (or something similar, such as no_expand_call(Goal)) … it also means that I can turn off goal expansion for specific goals in my source code.

I pushed a couple of changes for evaluation. They do not follow the @/1 rule, but try to be clever by avoiding expanding the same goal. There is some virtue in @/1, but there are also a couple of disadvantages:

  • You have to explain it.
  • It leads to ambiguity.
  • You typically do want other expansions to work on arguments. This implies further goal expansion for meta-predicates and function expansion in general.
  • It requires an extra pass to get rid of the @/1

Below is the new doc with an example. Please give it a try.

expand_goal(+Goal1, -Goal2)
This predicate is normally called by the compiler to perform preprocessing using
goal_expansion/2. The predicate computes a fixed-point by applying transformations until
there are no more changes. If optimisation is enabled (see -O and optimise), expand_goal/2
simplifies the result by removing unneeded calls to true/0 and fail/0 as well as trivially
unreachable branches.
If goal_expansion/2 wraps a goal as in the example below the system still reaches
fixed-point as it prevents re-expanding the expanded term while recursing. It does re-enable
expansion on the arguments of the expanded goal as illustrated in t2/1 in the example.

    :- meta_predicate run(0).
    
    may_not_fail(test(_)).
    may_not_fail(run(_)).
    
    goal_expansion(G, (G *-> true ; error(goal_failed(G),_))) :-
        may_not_fail(G).
    
    t1(X) :- test(X).
    t2(X) :- run(run(X)).

Is expanded into

    t1(X) :-
        (   test(X)
        *-> true
        ;   error(goal_failed(test(X)), _)
        ).
    
    t2(X) :-
        (   run((run(X)*->true;error(goal_failed(run(X)), _)))
        *-> true
        ;   error(goal_failed(run(run(X))), _)
        ).
1 Like

That’s good progress. Applied similar changes to the Logtalk goal-expansion mechanism, acknowledging this discussion. These changes don’t provide a solution that allows the user to mark a goal to be skipped when performing goal-expansion, however (that actually have always been possible in Logtalk by using the {}/1 compiler bypass control construct; but the semantics are not the same as the suggested @/1 marker).

So far I failed to see the need for such a construct. I surely acknowledge there are some cases where it is hard to control the expansion. I also fear that simply allowing people to prohibit further expansion can easily lead to rather unexpected results.

As we know, SWI-Prolog’s expansion still has some stuff to be resolved though …

@pmoura – is Logtalk’s {}/1 different from the “do not expand this goal” meaning for DCGs?

@jan – what happens when a goal is expanded by two different rules (e.g., it’s subject to DCG-like expansion plus rdet expansion)?
Also, is *-> the same as ->? (I couldn’t find it in the swipl docs, nor by a Google search)

goal expansion happens after DCG expansion, so that should be fine. What might be a problem is multiple goal_expansion rules in module pipeline. Not sure what the desired expansion should be in case of conflicts.

*-> is at http://www.swi-prolog.org/pldoc/doc_for?object=(*-%3E)/2. A simple search did the trick. Auto-completion in the search box not :frowning:

DCG expansion happening before goal expansion doesn’t help me because I use pack(edcg) instead of DCG.

I thought that the reason for expanding until a fixed point was to avoid the need to specify the order in which the goal expansion rules were applied …

1 Like

@peter.ludemann As you guessed, Logtalk’s {}/1 compiler bypass control construct is indeed inspired by the use of {}/1 in DCGs. In a source file, a term or a goal wrapped with {}/1 will neither be expanded or compiled but taken as is. More details at https://logtalk.org/manuals/refman/control/external_call_1.html You also mention the case where a goal can be expanded by two or more rules. I suspect there will be cases where the changes Jan and me implemented to avoid infinite goal-expansion loops may not be enough and we may need to check not only the goal but also the goal_expansion/2 clause or entity that expanded it earlier and decide if expansion should terminate or possibly continue with other applicable expansions.

@jan My take on multiple expansions is, as we discussed in the past and as implemented in Logtalk, to allow the user to specify the exact expansion flow. Logtalk’s concept of hook objects (https://logtalk.org/manuals/userman/expansion.html#hook-objects) should be implementable in SWI-Prolog without breaking backward compatibility. The library support for hook flows (https://logtalk.org/library/hook_pipeline_1.html and https://logtalk.org/library/hook_set_1.html) illustrates some of the possibilities (an usage example is available at https://github.com/LogtalkDotOrg/logtalk3/tree/master/examples/expansion).

Sometimes you do need/want to fully specify the order for intended results.

All term expansion is before goal expansion.

I did a quick test of swipl 8.1.3, by modifying library(rdet) to not check for a “marker”, and it works.

/*
You can implement a functor that does nothing but call whatever is passed to it ,
then in Your goal expansion promote Your expansion to use that functor ,
now Your goal expansion can check if a goal has already been promoted to use Your functor ,
in which case the expansion has already been done .

Example below rewrites every goal to use the “expanded” predicate
and does not rewrite any goal that is already an “expanded” goal .

IMHO it is a mistake to make the behaviour of goal_expansion different at a system level to tackle this problem .
A user may wish to see that goal come back again .
For example perhaps their implementation in goal_expansion uses assert or global variables
such that the second time around a different expansion is provoked .

~~~~~~~~ %&ZHcx;. ~~~~~~~~
*/

/*
?- [user] .
*/

expanded(_anything_) :- _anything_ .

goal_expansion(_saw_,_now_) :-
\+ _saw_ =.. [expanded|_] ,
my_goal_expansion(_saw_,_NOW_) ,
_now_ = expanded(_NOW_)  .

my_goal_expansion(hello,writeln('hello')) .

my_goal_expansion(goodbye,writeln('goodbye')) .

test :-
hello ,
goodbye .


/*
end_of_file.

?- test .
hello
goodbye
true.

?- expand_goal(hello,G) .
G = expanded(writeln(hello)).

?- expand_goal(goodbye,G).
G = expanded(writeln(goodbye)).

?- expand_goal(whatever,G).
G = whatever.

?- [user] .
*/
my_goal_expansion(_saw_,_now_) :-
_enabled_ = tabling(enabled(_saw_)) ,
_stored_ = tabling(stored(_saw_)) ,
_store_ = assertz(tabling(stored(_saw_))) ,
_1_ = (\+ _enabled_ , _saw_ ) ,
_2_ = (_enabled_ , _stored_ ) ,
_3_ = (_enabled_ , \+ _stored_ , _saw_ , _store_) ,
_now_ = (_1_ ; _2_ ; _3_)  .

tabling(enabled(foo(_))) .

foo(N) :-
between(0,10,N) ,
writeln(foo(N)) .

main :-
foo(N) ,
format("~N~10r~n",[N]) ,
false ;
true  .
/*
end_of_file.

?- main .
0
1
2
3
4
5
6
7
8
9
10

?- tabling(stored(T)) , format("~N~q.~n",[T]) , false ; true .
foo(0).
foo(1).
foo(2).
foo(3).
foo(4).
foo(5).
foo(6).
foo(7).
foo(8).
foo(9).
foo(10).
*/

I’m the author or rdet but I have been away for a while and was not able to closely follow the discussion. In one of the earlier discussions, there was suggested a different rewriting scheme, to wrap goals instead of calls. I believe that would make the issue go away as we don’t have to expand the same thing in the same predicate body again. Calls were wrapped to have better error reporting (you know in which pred body it happens). This is not necessary when stacktraces are enabled for error reporting.

The check for wrapping a call is a clever solution but only works in recent versions of SWI.

Any scheme of wrapping goals/calls must also have good runtime performance. The rewriting scheme with wrapping calls actually enhanced performance 40-50%. I believe that if-then-else provided the compiler some hints to emit a faster set of instructions when full non-determinism was not anymore needed.

I’m going to explore the options and their performance implications, in both -O and normal modes.

For my code, I didn’t notice any significant performance change with/without rdet (I see about +/-5% variation in speed despite my code being about 90% CPU bound, and rdet was “in the noise”). My guess is that most of my predicates are deterministic anyway (the remainder are either tests or shallow generators), so there’s seldom a choice point to remove by the (Goal->true;throw) expansion.

It is on my wish list to add something for that at the machine level. Basically dynamically modify the predicate prologue instructions (that is easy, as JIT indexing uses that too) to call a wrapper. That would allow for quick and easy dynamic (un)wrapping of predicates. This is a great help for debugging and I also need it for a faster and more robust implementation of tabling.

1 Like