Martim Correia
Martim Correia

Reputation: 505

checking if two lists have common elements

So basically, I have a predicate called common_elements(List1,List2), and the purpose of this predicate is to check if List1 has at least an element that belongs in List2.

Example:

?- common_elements([1,2,3,4,5,6],[6]).
true.

?- common_elements([1,2,3],[2]).
true.

?- common_elements([1,2,3],[6]).
false.

?- common_elements([P1,P2,P3,P4,P5,P6],[P7,P8,P6]).
true.

So for numbers this works well, but if i type variables it unifies the variables instead of checking if they are in the 2nd list.

Example:

?- common_elements([1,2,3],[2]).
true.

?- common_elements([1,2,3],[6]).
false.

?- common_elements([P1,P2,P3,P4,P5,P6],[P7,P8,P6]).
P1 = P7.

So as you can see for numbers it works well, but for some reason if type variables it unifies them instead of just comparing them and dont seem tu understand why.

Program:

common_elements(L1,L2) :- common_elements(L1,L2,[]).

common_elements([],_,AC) :- length(AC,C),
                            C >= 1.

common_elements([P|_],L2,AC) :- member(P,L2),!,
                                append(AC,[P],NAC),
                                common_elements([],L2,NAC).

common_elements([P|R],L2,AC) :- \+ member(P,L2),!,
                                common_elements(R,L2,AC).

Upvotes: 1

Views: 1679

Answers (2)

Paul Brown
Paul Brown

Reputation: 2403

Using builtins, as you've tagged SWI and ordsets is underappreciated

:- use_module(library(ordsets)).

common_elements(A, B) :-
    sort(A, AS), % can omit if using sorted A list
    sort(B, BS), % can omit if using sorted B list
    ord_intersect(As, Bs).

Some examples:

t1 :-
    common_elements([a, b, c], [d, e, f]).

t2 :-
    common_elements([a, b, c], [c, d, e]).

t3 :-
    common_elements([a, b, c], [_A, _B, _C]).

t4 :-
    common_elements([a, b, C], [d, e, C]).

t5 :-
    common_elements([a, b, _C], [d, e, _F]).

tests :-
    \+ t1,
         t2,
    \+ t3, 
         t4, 
    \+ t5.

Note: Use sort/2 rather than list_to_set/2 because the latter leaves variables in place. Also, use ord_intersect/2 over intersection/3 as the latter can produce unexpected results. If you use many set operations you may find it worthwhile using ordered lists (ordsets) throughout.

Upvotes: 3

willeM_ Van Onsem
willeM_ Van Onsem

Reputation: 476557

The member/2 predicate will perform unification. Indeed, for example:

?- member(P1, [P2]).
P1 = P2.

You can make use of ==/2 to avoid unification, and thus:

True if Term1 is equivalent to Term2. A variable is only identical to a sharing variable.

So what we can here do is check if a variable is equivalent to another variable with:

membereq(X, [H|_]) :-
    X == H.
membereq(X, [_|T]) :-
    membereq(X, T).

Then we thus can check:

common_elements([H|_], L2) :-
    membereq(H, L2).
common_elements([_|T], L2) :-
    common_elements(T, L2).

This then answers the queries with:

?- common_elements([1,2,3,4,5,6],[6]).
true ;
false.

?- common_elements([1,2,3,4,5,6],[6]).
true ;
false.

?- common_elements([1,2,3],[2]).
true ;
false.

?- common_elements([1,2,3],[6]).
false.

?- common_elements([P1,P2,P3,P4,P5,P6],[P7,P8,P6]).
true ;
false.

Upvotes: 3

Related Questions