Prolog substitution

2020-04-18 09:14发布

问题:

How can I replace a list with another list that contain the variable to be replaced. for example

rep([x, d, e, z, x, z, p], [x=z, z=x, d=c], R).
R = [z, c, e, x, z, x, p]

the x to z and z doesn't change after it has been replaced.

so far I did only the one without the list

rep([], _, []).
rep(L1, H1=H2, L2) :-
   rep(L1, H1, H2, L2).

rep([],_,_,[]).
rep([H|T], X1, X2, [X2|L]) :-
   H=X1,
   rep(T,X1,X2,L),
   !.
rep([H|T],X1,X2,[H|L]) :-
   rep(T,X1,X2,L).

回答1:

I find your code rather confused. For one thing, you have rep/3 and rep/4, but none of them have a list in the second position where you're passing the list of variable bindings. H1=H2 cannot possibly match a list, and that's the only rep/3 clause that examines the second argument. If this is a class assignment, it looks like you're a little bit behind and I'd suggest you spend some time on the previous material.

The solution is simpler than you'd think:

rep([], _, []).
rep([X|Xs], Vars, [Y|Rest]) :-    member(X=Y, Vars), rep(Xs, Vars, Rest).
rep([X|Xs], Vars, [X|Rest]) :- \+ member(X=_, Vars), rep(Xs, Vars, Rest).

We're using member/2 to find a "variable binding" in the list (in quotes because these are atoms and not true Prolog variables). If it's in the list, Y is the replacement, otherwise we keep using X. And you see this has the desired effect:

?- rep([x, d, e, z, x, z, p], [x=z, z=x, d=c], R).
R = [z, c, e, x, z, x, p] ;
false.

This could be made somewhat more efficient using "or" directly (and save us a choice point):

rep([], _, []).
rep([X|Xs], Vars, [Y|Ys]) :- 
  (member(X=Y, Vars), ! ; X=Y), 
  rep(Xs, Vars, Ys).

See:

?- rep([x, d, e, z, x, z, p], [x=z, z=x, d=c], R).
R = [z, c, e, x, z, x, p].


回答2:

If you use SWI-Prolog, with module lambda.pl found there : http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/lambda.pl you can write :

:- use_module(library(lambda)).

rep(L, Rep, New_L) :-
    maplist(\X^Y^(member(X=Z, Rep)
              ->  Y = Z
              ;   Y = X), L, New_L).


回答3:

You should attempt to keep the code simpler than possible:

rep([], _, []).
rep([X|Xs], Vs, [Y|Ys]) :-
   ( memberchk(X=V, Vs) -> Y = V ; Y = X ),
   rep(Xs, Vs, Ys).

Of course, note the idiomatic way (thru memberchk/2) to check for a variable value.

Still yet a more idiomatic way to do: transforming lists it's a basic building block in several languages, and Prolog is no exception:

rep(Xs, Vs, Ys) :- maplist(repv(Vs), Xs, Ys).
repv(Vs, X, Y) :- memberchk(X=V, Vs) -> Y = V ; Y = X .


回答4:

Here's how you could proceed using if_/3 and (=)/3.

First, we try to find a single Key in a list of pairs K-V. An extra argument reifies search success.

pairs_key_firstvalue_t([]       ,_  ,_    ,false).
pairs_key_firstvalue_t([K-V|KVs],Key,Value,Truth) :-
   if_(K=Key,
       (V=Value, Truth=true),
       pairs_key_firstvalue_t(KVs,Key,Value,Truth)).

Next, we need to handle "not found" cases:

assoc_key_mapped(Assoc,Key,Value) :-
   if_(pairs_key_firstvalue_t(Assoc,Key,Value),
       true,
       Key=Value).

Last, we put it all together using the meta-predicate maplist/3:

?- maplist(assoc_key_mapped([x-z,z-x,d-c]), [x,d,e,z,a,z,p], Rs).
Rs = [z,c,e,x,a,x,p].                       % OK, succeeds deterministically


回答5:

Let's improve this answer by moving the "recursive part" into meta-predicate find_first_in_t/4:

:- meta_predicate find_first_in_t(2,?,?,?).
find_first_in_t(P_2,X,Xs,Truth) :-
   list_first_suchthat_t(Xs,X,P_2,Truth).

list_first_suchthat_t([]    ,_, _ ,false).
list_first_suchthat_t([E|Es],X,P_2,Truth) :-
   if_(call(P_2,E),
       (E=X,Truth=true),
       list_first_suchthat_t(Es,X,P_2,Truth)).

To fill in the "missing bits and pieces", we define key_pair_t/3:

key_pair_t(Key,K-_,Truth) :-
   =(Key,K,Truth).

Based on find_first_in_t/4 and key_pair_t/3, we can write assoc_key_mapped/3 like this:

assoc_key_mapped(Assoc,Key,Value) :-
   if_(find_first_in_t(key_pair_t(Key),_-Value,Assoc),
       true,
       Key=Value).

So, does the OP's use-case still work?

?- maplist(assoc_key_mapped([x-z,z-x,d-c]), [x,d,e,z,a,z,p], Rs).
Rs = [z,c,e,x,a,x,p].                            % OK. same result as before

Building on find_first_in_t/4

memberd_t(X,Xs,Truth) :-                        % memberd_t/3
   find_first_in_t(=(X),_,Xs,Truth).

:- meta_predicate exists_in_t(2,?,?).           % exists_in_t/3
exists_in_t(P_2,Xs,Truth) :-
   find_first_in_t(P_2,_,Xs,Truth).


回答6:

An approach that turns connectives or predicates into truth functionals, i.e. for a connective or predicate XX of arity n, the attempt is to make a predicate XX_t of arity n+1, with the last argument from the domain {true,false}, there are severe limitations if this approach is based on the ISO standard.

One typical limitation is that these predicates cannot so easily cut away branches of (;)/2. The normal cut (!) would also affect the surrounding of (;)/2 since (;)/2 is cut transparent.

What would be needed is a local cut (sys_local_cut), which can affect cut transparent predicates locally. So I guess this is the blind spot of all this look see I have a XX_t predicate, but it leaves to many choice points.

The problem is that local cut (sys_local_cut) is not in the ISO standard. But I guess if the developers of XX_t connnectiveswould have such means that would reach the same choice point behaviour as the original XX connnectives.

Bye