简体   繁体   中英

Perfoming member check on a difference list, but how?

I tried to answer another question (wrongly though) and this led to a question on "difference lists" (or "list differences", which seems a more appropriate name, unless "Escherian Construction" isn't preferred)

We have a fully ground list of elements obj(X,Y) (both X and Y ground). We want to retain only the first obj(X,_) where X hasn't been encountered yet when going through the list front to back. Those "first elements" must appear in order of appearance in the result.

Let's specify the problem through test cases:

% Testing

:- begin_tests(collapse_dl).   

test(one)   :- collapse_dl([],[]).
test(two)   :- collapse_dl([obj(a,b)],
                           [obj(a,b)]).
test(three) :- collapse_dl([obj(a,b),obj(a,c)],
                           [obj(a,b)]).
test(four)  :- collapse_dl([obj(a,b),obj(a,c),obj(b,j)],
                           [obj(a,b),obj(b,j)]).
test(five)  :- collapse_dl([obj(a,b),obj(a,c),obj(b,j),obj(a,x),obj(b,y)],
                           [obj(a,b),obj(b,j)]).

:- end_tests(collapse_dl).

rt :- run_tests(collapse_dl).

Now, this is easy to implement using filtering, list prepend and reverse/2 , but what about using difference lists and list append ?

however, I'm not able to get the seen/2 predicate to work. It checks whether obj(A,_) is already in the difference list. But what's a proper termination for this predicate?

% This is called

collapse_dl([],[]) :- !. 
collapse_dl([X|Xs],Out) :-
   Dlist = [X|Back]-Back,        % create a difflist for the result; X is surely in there (as not yet seen) 
   collapse_dl(Xs,Dlist,Out).    % call helper predicate  

% Helper predicate

collapse_dl([],Ldown,Lup):-               % end of recursion; bounce proper list back up
   Ldown = Lup-[].                        % the "back" of the difflist is unified with [], so "front" becomes a real list, and is also Lup                    

collapse_dl([obj(A,_)|Objs],Ldown,Out) :- 
   seen(obj(A,_),Ldown),                  % guard: already seen in Ldown?
   !,                                     % then commit
   collapse_dl(Objs,Ldown,Out).           % move down chain of induction

collapse_dl([obj(A,B)|Objs],Ldown,Out) :-
   \+seen(obj(A,_),Ldown),                % guard: not yet seen in Ldown?
   !,                                     % then commit
   Ldown = Front-Back,                    % decompose difference list   
   Back = [obj(A,B)|NewTail],             % NewTail is fresh! Append via difflist unification magic
   collapse_dl(Objs,Front-NewTail,Out).   % move down chain of induction; Front has been refined to a longer list

% Membership check in a difference list 

seen(obj(A,_),[obj(A,_)|_Objs]-[]) :- !.  % Yup, it's in there. Cut retry.
seen(Obj,[_|Objs]-[]) :- ...              % But now???

Update

With Paulo's code snippet:


% Membership check in a difference list 

seen(Element, List-Back) :-
    List \== Back,
    List = [Element|_].    
seen(Element, List-Back) :-
    List \== Back,
    List = [_| Tail],
    seen(Element, Tail-Back).

So, term equivalence , or dis-equivalence in this case, is the solution!

We now pass all the test.

Try (taken from Logtalk difflist library object):

member(Element, List-Back) :-
    List \== Back,
    List = [Element|_].
member(Element, List-Back) :-
    List \== Back,
    List = [_| Tail],
    member(Element, Tail-Back).

memberchk/2 should do it. Using the approach from here ,

%% collapse_dl( ++Full, -Short )
collapse_dl( [obj(K,V) | A], B ) :-
    memberchk( obj(K,X), B ),
    ( X = V -> true ; true ),
    collapse_dl( A, B ).
collapse_dl( [], B ) :-
    length( B, _), !.

Doing what (functional) Prolog does best, instantiating an open-ended list in a top-down manner.

Passes the tests included in the question.


Addendum: With printouts

%% collapse_dl( ++Full, -Short )
collapse_dl( [obj(K,V) | A], B ) :-
    format("Enter : ~w relatedto ~w\n", [[obj(K,V) | A], B]),
          % Necessarily find  (find or insert)  obj(K, X) (thanks to the 
          %  uninstantiated X) in list B which has an "unobserved" tail:
    memberchk( obj(K,X), B ),
          % Unify X with V if you can; ignore failure if you can't!
    ( X = V -> true ; true ),
    format("Mid   : ~w relatedto ~w\n", [[obj(K,V) | A], B]),
    collapse_dl( A, B ),
    format("Return: ~w relatedto ~w\n", [[obj(K,V) | A], B]).

collapse_dl( [], B ) :-
    format("Termination: From unobserved-tail-list ~w ",[B]),
    length(B, _), 
    format("to ~w (and don't come back!)\n",[B]),
    !.

Because of the added printouts this code is no longer tail-recursive. The original is, and so has no "return" in its trace: it just goes forward and stops working right away when the input list is traversed to its end.

See more about the distinction eg here .


This "open-ended list" technique is not difference list, but the two are very closely related. And we don't actually need the explicit tail anywhere here, except for the final freezing. So we just do the O(n) length call instead of the explicit O(1) Tail = [] we'd do with difference lists, no biggie.

Of bigger impact is the choice of list instead of eg tree data structure. Trees can be open-ended too, just need to use var/1 here and there. Next step is the tree's structure. Top-down open-leaved tree can't be rotated (as all the calls reference the same top node) so its depth will depend on the input's orderedness. To maintain good balance the trees need to be rotated on occasion, hence closed; and we're back to the traditional state-passing code, were each call gets two tree arguments -- the one before update, and the other after it: the

    upd(T1, T2), next(T2, T3), more(T3, T4), ... 

kind of thing. It ought to be used in real code. There are some libraries that do that.

This answer's code is simplistic, in order to be simple and illustrative.

Since I currently need it, I got a simpler solution. Assuming the difference list is open, means for the pair List-Back , we have var(Back) . Then we can short cut, only passing List :

member_open(_, List) :- var(List), !, fail.
member_open(Element, [Element|_]).
member_open(Element, [_|List]) :- member_open(Element, List).

If we want to append an element to the List , since for example we didn't find it via member_open/2, we simply make Back = [NewElement|Back2] and continue with Back2 .

Here is variables/2 (ISO term_variables/2 ) written this way, so that it doesn't need reverse/1:

variables(T, L) :-
   variables(T, B, B, B2),
   B2 = [],
   L = B.

variables(V, L, B, B) :- var(V), member_open(W, L), V == W, !.
variables(V, L, [V|B], B) :- var(V), !.
variables(T, L, B, B2) :-
   T =.. [_|A],
   variables_list(A, L, B, B2).

variables_list([T|A], L, B, B2) :-
   variables(T, L, B, H),
   variables_list(A, L, H, B2).
variables_list([], _, B, B).

Seems to work:

?- variables(f(X,g(X,Y),Y), L).
L = [X, Y].

The technical post webpages of this site follow the CC BY-SA 4.0 protocol. If you need to reprint, please indicate the site URL or the original address.Any question please contact:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM