7

I need to write a program that finds the intersection of two lists. I can't use cuts and there shouldn't be any duplicate elements in the result list.

This is my code:

intersection([],_,[]).
intersection([X|Xs],Y,[X|Zs]) :-
    member(X,Y),
    intersection(Xs,Y,Zs).
intersection([_|Xs],Y,Zs) :-
    intersection(Xs,Y,Zs).

When I run the following query, I get these answers:

?- intersection([a,b,c,a],[a,v,c],L).
L = [a, c, a] ;
L = [a, c] ;            % <---------- this is only answer I want to get
L = [a, a] ;
L = [a] ;
L = [c, a] ;
L = [c] ;
L = [a] ;
L = [].

What can I do? I want to get L = [a,c] and nothing else... Can you help?

Mousey
  • 1,855
  • 19
  • 34
nofar mishraki
  • 526
  • 1
  • 4
  • 15
  • 3
    It is not entirely clear what you mean by "conjunction". Do you mean "intersection"? –  Jul 26 '15 at 16:19

5 Answers5

6

In my answer to the related question "Intersection and union of 2 lists" I presented the logically pure predicate list_list_intersectionSet/3. It should fit your requirements to a T!

Here's is a brushed-up version of list_list_intersectionSet/3, which is based on:

Here we go:

list_list_intersectionSet([]     ,_ ,[]).
list_list_intersectionSet([A|As0],Bs,Cs0) :-
   if_(memberd_t(A,Bs), Cs0 = [A|Cs], Cs0 = Cs),
   tfilter(dif(A),As0,As), 
   list_list_intersectionSet(As,Bs,Cs).

Let's see it in action!

?- list_list_intersectionSet([a,b,c,a],[a,v,c],L).
L = [a,c].
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
3

If by "conjunction" you mean "intersection", you should take a look at the implementation in the SWI-Prolog library(lists) of the predicate intersection/3. It contains cuts, but you can leave them out if you don't mind all the choicepoints.

With it:

?- intersection([a,b,c,a],[a,v,c],I).
I = [a, c, a].

Of course, this doesn't work even in the library predicate, because you need sets with your current definition. (It is enough if only the first argument is a set.)

You can make sets with the sort/2 predicate: if the first argument is a list with repetitions, the second argument will be a sorted list without repetitions, for example:

?- sort([a,b,c,a], S1), intersection(S1, [a,v,c], I).
S1 = [a, b, c],
I = [a, c].

or maybe:

?- sort([a,b,c,a], S1), intersection(S1, [a,v,c,c,a,c], I).
S1 = [a, b, c],
I = [a, c].

?- sort([a,b,c,a,b,c,a,b,c], S1), intersection(S1, [a,v,c,c,a,c], I).
S1 = [a, b, c],
I = [a, c].

If you sort both arguments, you can use a ord_intersection/3 from library(ordsets), implemented in terms of oset_int/3.

?- sort([a,b,c,a], S1), sort([a,v,c,c,a,c], S2), ord_intersection(S1, S2, I).
S1 = [a, b, c],
S2 = [a, c, v],
I = [a, c].

Importantly, oset_int/3 does not use any cuts in its implementation. It however assumes that the first and second arguments are lists of elements sorted by the "standard order of terms" and without duplicates, as done by sort/2.

If for some reason you don't want to use sort/2, you could maybe use an accumulator and check against it before taking an element to the intersection:

my_intersection(Xs, Ys, Zs) :-
    my_intersection_1(Xs, Ys, [], Zs).
my_intersection_1([], _, Zs, Zs).
my_intersection_1([X|Xs], Ys, Zs0, Zs) :-
    member(X, Ys), \+ member(X, Zs0),
    my_intersection_1(Xs, Ys, [X|Zs0], Zs).
my_intersection_1([_|Xs], Ys, Zs0, Zs) :-
    my_intersection_1(Xs, Ys, Zs0, Zs).

Of course, the order of the elements in the result will be now reversed. If this is not what you mean by "conjunction", you could for example rewrite the first two clauses of my_intersection_1/4 as:

my_intersection_1([], _, _, []).
my_intersection_1([X|Xs], Ys, Zs0, [X|Zs]) :-
    member(X, Ys), \+ member(X, Zs0),
    my_intersection_1(Xs, Ys, [X|Zs0], Zs).
3

The previously shown list_list_intersectionSet/3 restricts the item order in the intersection:

?- list_list_intersectionSet([a,b],[a,b], [a,b]).
true.

?- list_list_intersectionSet([a,b],[a,b], [b,a]).
false.

In this answer we lift that restriction... preserving and determinism (for ground cases)!

First, we define none_intersect/2 using Prolog lambdas and maplist/2.

none_intersect(As,Bs) states that all members in As are different from all members in Bs.

:- use_module(library(lambda)).

none_intersect(As,Bs) :-
   maplist(\A^maplist(dif(A),Bs),As).

Next, we define intersection_of_and/3---based on none_intersect/2 (defined above), tpartition/4 and reified term equality (=)/3:

intersection_of_and([],As,Bs) :-
   none_intersect(As,Bs).
intersection_of_and([X|Xs],As0,Bs0) :-
   tpartition(=(X),As0,[_|_],As),        % [_|_] = [X|_]
   tpartition(=(X),Bs0,[_|_],Bs),        % [_|_] = [X|_]
   intersection_of_and(Xs,As,Bs).

intersection_of_and(Xs,As,Bs) states that

  • all items which occur in both As and Bs also occur in Xs (first clause),
  • all items in Xs occur in both As and Bs at least once (second clause),
  • and the list Xs does not contain any duplicates.

intersection_of_and/3 uses a specific argument in order to enable first argument indexing.

Last, we define list_list_intersection/3 which has the argument order that the OP used:

list_list_intersection(As,Bs,Xs) :-
   intersection_of_and(Xs,As,Bs).

Let's run some queries! First, the query that the bounty offerer suggested:

?- list_list_intersection([a,b],[a,b], [b,a]).
true.

Next, a similar query with 3 distinct items in 3 lists having 3 different orders:

?- list_list_intersection([a,b,c],[b,a,c], [c,a,b]).
true.

What if some x only occurs in the first/second list?

?- list_list_intersection([a,b,c,x],[b,a,c], [c,a,b]).
true.

?- list_list_intersection([a,b,c],[b,a,c,x], [c,a,b]).
true.

What if some item occurs twice in the first/second list?

?- list_list_intersection([a,b,c],[b,a,c,b], [c,a,b]).
true.

?- list_list_intersection([a,b,c,c],[b,a,c], [c,a,b]).
true.

Last, what if the intersection contains duplicates? Intersections are not to contain duplicates...

?- list_list_intersection([a,b,c],[b,a,c], [c,c,a,b]).
false.                                     % as expected
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
0

Seems like something like this would be the easy way:

intersection( Xs , Ys , Zs ) :-
  sort(Xs,X1)     , % order and de-dupe the 1st list so as to produce a set
  sort(Ys,Y1)     , % order and de-dupe the 2nd list so as to produce a set
  merge(Xs,Ys,Zs)   % merge the two [ordered] sets to produce the result
  .                 % easy!

merge( []     , []     , []     ) .
merge( []     , [_|_]  , []     ) .
merge( [_|_]  , []     , []     ) .
merge( [X|Xs] , [Y|Ys] , [X|Zs] ) :- X =  Y , merge(    Xs  ,    Ys  , Zs ) .
merge( [X|Xs] , [Y|Ys] , Zs     ) :- X <  Y , merge(    Xs  , [Y|Ys] , Zs ) .
merge( [X|Xs] , [Y|Ys] , Zs     ) :- X >  Y , merge( [X|Xs] ,    Ys  , Zs ) .

Or even just this [not-terribly-performant] one-liner:

intersection( Xs , Ys , Zs ) :- setof(Z,(member(Z,Xs),member(Z,Ys)),Zs).
Nicholas Carey
  • 71,308
  • 16
  • 93
  • 135
0

This can be solved by simple set theory:

    intersection(A,B,AnB):-
        subtract(A,B,AminusB),
        subtract(A,AminusB,K),
        sort(K,AnB).

For the query:

   ?- intersection([a,b,c,a],[a,v,c],L).

output is

    L = [a, c].

No more answers.

Vikram Venkat
  • 663
  • 4
  • 16