On mixing Prolog coroutining (freeze/2, when/2) and DCG

104 Views Asked by At

In my previous answer to the recent question "Prolog binary search tree test - unwanted parents' parent node comparison", I proposed mixing lazy_chain/2 which uses ...

:- use_module(library(clpfd)).

lazy_chain(Zs, R_2) :-
   (  var(R_2)                  -> instantiation_error(R_2)
   ;  clpfd:chain_relation(R_2) -> freeze(Zs, lazy_chain_aux(Zs,R_2))
   ;  otherwise                 -> domain_error(chain_relation, R_2)
   ).

lazy_chain_aux([], _).
lazy_chain_aux([Z0|Zs], R_2) :-
   freeze(Zs, lazy_chain_aux_(Zs,R_2,Z0)).

lazy_chain_aux_([], _, _).
lazy_chain_aux_([Z1|Zs], R_2, Z0) :-
   call(R_2, Z0, Z1),
   freeze(Zs, lazy_chain_aux_(Zs,R_2,Z1)).

... together with in_order//1 ...

in_order(nil) --> [].
in_order(node(X,L,R)) --> in_order(L), [X], in_order(R).

... like so:

?- lazy_chain(Zs, #<),
   phrase(in_order(node(1,nil,nil)), Zs).
Zs = [1,23].

Is there a easy way to "push" lazy_chain into phrase/3 so that its scope is limited to the part of the sequence described by in_order//1?

Right now, I get ...

?- lazy_chain(Zs, #<),
   phrase(in_order(node(1,nil,nil)), Zs0,Zs).
Zs0 = [1|Zs], freeze(Zs, lazy_chain_aux(Zs,#<)).

... which (of course) can fail upon further instantiation of Zs:

?- lazy_chain(Zs, #<),
   phrase(in_order(node(1,nil,nil)), Zs0,Zs),
   Zs = [3,2,1].
false.

How can I work around that and constrain lazy_chain to the part of the ?

2

There are 2 best solutions below

0
On BEST ANSWER

In the meantime I came up with the following hack:

lazy_chain_upto(R_2, P_2, Xs0, Xs) :-
   (  var(R_2)                  -> instantiation_error(R_2)
   ;  clpfd:chain_relation(R_2) -> when((nonvar(Xs0) ; ?=(Xs0,Xs)),
                                        lazy_chain_upto_aux(Xs0,Xs,R_2)),
                                   phrase(P_2, Xs0, Xs)
   ;  otherwise                 -> domain_error(chain_relation, R_2)
   ).

lazy_chain_upto_aux(Xs0, Xs, _) :-
   Xs0 == Xs,
   !.
lazy_chain_upto_aux([], _, _).
lazy_chain_upto_aux([X|Xs0], Xs, R_2) :-
   when((nonvar(Xs0) ; ?=(Xs0,Xs)), lazy_chain_upto_prev_aux(Xs0,Xs,R_2,X)).

lazy_chain_upto_prev_aux(Xs0, Xs, _, _) :-
   Xs0 == Xs,
   !.
lazy_chain_upto_prev_aux([], _, _, _).
lazy_chain_upto_prev_aux([B|Xs0], Xs, R_2, A) :-
   call(R_2, A, B),
   when((nonvar(Xs0) ; ?=(Xs0,Xs)), lazy_chain_upto_prev_aux(Xs0,Xs,R_2,B)).

Based on this we could define in_orderX//1 like this:

in_orderX(T) --> lazy_chain_upto(#<, in_order(T)).

The sample query shown in the question ...

?- phrase(in_orderX(node(1,nil,nil)), Zs0,Zs), Zs = [3,2,1].
Zs0 = [1,3,2,1], Zs = [3,2,1].

... now checks out alright, but still I wonder: is it worth it?

0
On

I don't see any problem mixing corouting and DCG. DCG is only a translation from the DCG rules H --> B, to some ordinary Prolog rules H' :- B'. Any constraint posting can be wrapped into {}/1.

Here is an example from Quines:

% eval(+Term, +List, -Term, +Integer)
eval([quote,X], _, X) --> [].
eval([cons,X,Y], E, [A|B]) -->
   step,
   eval(X, E, A),
   eval(Y, E, B).
eval([lambda,X,B], E, [closure,X,B,E]) --> [].
eval([X,Y], E, R) -->
   step,
   {neq(X, quote), sto(B)},
   eval(X, E, [closure,Z,B,F]),
   {sto(A)},
   eval(Y, E, A),
   eval(B, [Z-A|F], R).
eval(S, E, R) -->
   {freeze(S, is_symbol(S)), freeze(E, lookup(S, E, R))}.

You could do the same for lazy_chain_upto//2. As a start you could go on an define the first clause of lazy_chain_upto//2 as follows:

lazy_chain_upto(R_2, P_2) -->
   (  {var(R_2)}                  -> {instantiation_error(R_2)}
   ;  {clpfd:chain_relation(R_2)} -> /* ?? */
   ;  {otherwise}                 -> {domain_error(chain_relation, R_2)}
   )

In the /* ?? */ part you could profit from a DCG-ifyed lazy_chain_upto_aux//1 predicate as well. Of course I am assuming that the DCG translation understands (->) and (;)/2.

Bye