I need to do an exercise where I must eliminate the elements of a list that are NOT duplicated, previously I made one to eliminate the elements of a list that ARE duplicated. This is my code to eliminate the elements that ARE duplicated in a list but I don't know how to modify it to generate a new code to eliminate the elements of a list that are NOT duplicated. Can somebody help me? Please.
simp([H,H|T],X):-!, simp([H|T],X).
simp([H|T],[H|X]):-simp(T,X).
CodePudding user response:
Using reif library, to be both pure and reasonably deterministic (similar answer):
:- use_module(library(reif)).
duplicate_elements(LstFull, LstDuplicates) :-
duplicate_elements_(LstFull, [], LstDuplicatesRev),
reverse(LstDuplicatesRev, LstDuplicates).
duplicate_elements_([], L, L).
% U means LstUpto
duplicate_elements_([H|T], U, LstD) :-
memberd_t(H, T, Bool),
(Bool == true -> duplicate_elements_add_(U, H, U1) ; U1 = U),
duplicate_elements_(T, U1, LstD).
duplicate_elements_add_(U, E, U1) :-
% Prevent adding a duplicate to U1 more than once
(memberchk(E, U) -> U1 = U ; U1 = [E|U]).
Result in swi-prolog:
?- time(duplicate_elements([a,b,1,2,c,A,2,1,4], D)).
% 105 inferences, 0.000 CPU in 0.000 seconds (92% CPU, 1494726 Lips)
A = a,
D = [a,1,2] ;
% 177 inferences, 0.000 CPU in 0.000 seconds (94% CPU, 1261726 Lips)
A = b,
D = [b,1,2] ;
% 193 inferences, 0.000 CPU in 0.000 seconds (98% CPU, 1288643 Lips)
A = 1,
D = [1,2] ;
% 214 inferences, 0.000 CPU in 0.000 seconds (96% CPU, 1349996 Lips)
A = 2,
D = [1,2] ;
% 237 inferences, 0.000 CPU in 0.000 seconds (98% CPU, 1515152 Lips)
A = c,
D = [1,2,c] ;
% 360 inferences, 0.000 CPU in 0.000 seconds (99% CPU, 1892217 Lips)
A = 4,
D = [1,2,4] ;
% 49 inferences, 0.000 CPU in 0.000 seconds (95% CPU, 575563 Lips)
D = [1,2],
dif(A,a),
dif(A,4),
dif(A,c),
dif(A,2),
dif(A,1),
dif(A,b).
CodePudding user response:
First of all, your question is ambiguous, you said that
eliminate the elements of a list that are NOT duplicated
It should mean to remove the unique elements.
For example,
?- remove_unique_elems([a,b,1,2,c,a,2,1,4], R).
R = [a,1,2,a,2,1].
However, in the comment later, you also said that
If I write
?- eliminate([a,b,1,2,c,a,2,1,4], R).
. I wan to getR = [a,1,2].
That is not "remove the unique elements", but "get the duplicate elements as a 'set', but keep the original order".
Nevertheless, I will still give you two solutions:
Define
dup
to generate all duplicate elementsdelete(X,[X|L],L) :- !. delete(Y,[X|Xs],[X|Xt]) :- delete(Y,Xs,Xt). dup(X,L) :- member(X,L), delete(X,L,L2), memberchk(X,L2). ?- dup(X,[a,b,1,2,c,a,2,1,4]). X = a ; X = 1 ; X = 2 ; X = a ; X = 2 ; X = 1 ; false.; ?- dup(X,[1,2,3,4]). false.
Define
remove_unique_elems
remove_unique_elems(L,R) :- ( bagof(X, dup(X,L), Xs) -> R = Xs ; R = [] ). ?- remove_unique_elems([a,b,1,2,c,a,2,1,4], R). R = [a,1,2,a,2,1]. ?- remove_unique_elems([1,2,3,4], R). R = []. ?- remove_unique_elems([a,a],[a,a]). true.
Define
duplicate_elements
remove_dup(DL,NDL) :- reverse(DL, DLR), remove_dup_(DLR, NDLR),reverse(NDLR, NDL). remove_dup_([], []) :- !. remove_dup_([X|Xs], L) :- member(X, Xs), !, remove_dup_(Xs, L). remove_dup_([X|Xs], [X|Ys]) :- remove_dup_(Xs, Ys). duplicate_elements(L,R) :- ( bagof(X, dup(X,L), Xs) -> remove_dup(Xs, R) ; R = [] ). ?- duplicate_elements([a,b,1,2,c,a,2,1,4], R). R = [a,1,2]. ?- duplicate_elements([1,2,3,4], R). R = []. ?- duplicate_elements([a,a], [a,a]). false.