managing lists in prolog - list

Im new to Prolog and was looking for some assistance. What i am trying to do is basically get a list L consisting of elements that repeat at least twice in a given list L'
Example
L'=[1,2,1,3,4,3,2] => L=[1,2,3].
So far I am able to compute the occurrence of every consecutive variables
% pack(L1,L2) :- the list L2 is obtained from the list L1 by packing
% repeated occurrences of elements into separate sublists.
% (list,list) (+,?)
pack([],[]).
pack([X|Xs],[Z|Zs]) :- transfer(X,Xs,Ys,Z), pack(Ys,Zs).
% transfer(X,Xs,Ys,Z) Ys is the list that remains from the list Xs
% when all leading copies of X are removed and transfered to Z
transfer(X,[],[],[X]).
transfer(X,[Y|Ys],[Y|Ys],[X]) :- X \= Y.
transfer(X,[X|Xs],Ys,[X|Zs]) :- transfer(X,Xs,Ys,Zs).
% encode(L1,L2) :- the list L2 is obtained from the list L1 by run-length
% encoding. Consecutive duplicates of elements are encoded as terms [N,E],
% where N is the number of duplicates of the element E.
% (list,list) (+,?)
encode(L1,L2) :- pack(L1,L), transform(L,L2).
transform([],[]).
transform([[X|Xs]|Ys],[[N,X]|Zs]) :- length([X|Xs],N), transform(Ys,Zs).
which will return the following list of touples
?- encode([a,a,a,a,b,c,c,a,a,d,e,e,e,e],X).
X = [[4,a],[1,b],[2,c],[2,a],[1,d][4,e]]
But there still remains the problem of building a list that will contain distinct elements that repeat at least twice.
If anyone can help me or point me in the general direction that would be great.
Thanks in advance

an element E of list L should:
be a member of list L',
be a member of list L'' where L'' is list L' if we remove element E.
check select/3, member/2, findall/3 and/or setof/3

You could write a procedure:
% E it's the list of are elements from L that repeat at least twice
elements_that_repeat_at_least_twice(L, E) :-
elements_that_repeat_at_least_twice(L, [], E).
elements_that_repeat_at_least_twice([H|Ls], Dupl, E) :-
...
In elements_that_repeat_at_least_twice the added list Dupl will keep each element you verify it's present multiple times. Examine each element of L, using [H|Ls].
Use memberchk/2 to verify if H is in L: then it's at least duplicate. If it's not yet in Dupl, add to it, and recurse. Remember to write the recursion base case (stop at empty list []).
Now I see you have added some code: then I complete suggestion:
elements_that_repeat_at_least_twice([], Dupl, Dupl).
elements_that_repeat_at_least_twice([H|Ls], Dupl, E) :-
( memberchk(H, Ls)
-> ( \+ memberchk(H, Dupl)
-> Dupl1 = [H|Dupl]
; Dupl1 = Dupl
)
; Dupl1 = Dupl
),
elements_that_repeat_at_least_twice(Ls, Dupl1, E).
Remember to reverse the list of duplicates when done.

Related

Prolog: is there any way to generate the following items from a list?

I want to develop a predicate in prolog called next, which given a list returns another list with the N elements following the last value of the list where N is the size of the main list. For example: next([1,2,3,4], R).
will return R = [5,6,7,8]. or: next([11,12,13], R). It will return R = [14,15,16].
The problem I have is that if I iterate over the main list until I am left with its last element and start adding the next one to it to the result list, I don't know how many times I should iterate since I don't know what the length of the main list was.This is why my algorithm goes into a loop.
next([], []).
next([X], [X1|Res]) :- X1 is X + 1, next3([X1],Res),!.
next([H|T], [X]) :- next3(T, X).
How about this.
Here we use Constraint Logic Programming to constraint the elements of the result list to be increasing-monotonically-by-1 but just set them to actual values (in one instruction) once we know the last element of the input list.
We also use an open list (a list with an unbound fin) instead of append/3 to grow the output list at its end efficiently. This idiom called "using a difference list".
Finally we add test cases.
:- use_module(library(clpfd)).
% ---
% Called by the customer
% ---
nextor([],[]) :- !. % Empty input list means no work to do!
nextor([X|Xs],Out) :- % The input list contains at least 1 element
assertion(integer(X)), % This is for stating what we assume
OpenList = [K|Fin], % We will create a list of fresh variables; in order
% _to append easily, the list is kept "open", i.e. its tail end
% _is not [] as in a proper list but an unbound variable
% _(namely, Fin). The first element is as yet undefined,
% it is the fresh variable K.
assertion(\+is_list(OpenList)), % Not a list at present time.
nextor_w(X,Xs,[K|Fin],LastFin,LastX), % Processing the list with the first element X already
% _separated out (for assertions). To grow the OpenList at
% _its end, we just need Fin (we don't care about that list's
% Tip when we grow it at the end). Finally, to communicate
% the last Fin set up in the depth of the recursion to this
% call place, use LastFin. The last X found will be in LastX.
LastFin=[], % The open list is close (made proper list) by setting its
% _final Fin to [].
assertion(is_list(OpenList)), % Yes, it is a list now!
K #= LastX+1, % Now that LastX is known, we know K too.
% _The constraint propagates down the list, fixing the still
% unbound variables in OpenList (which is now a closed list).
Out = OpenList. % Unify for result.
% ---
% Does the recursion down the input list
% ---
nextor_w(Xp,[],[_|Fin],Fin,Xp) :- !. % At the end of recursion, communicate the "last X" and the
% and the "latest Fin" back to the caller.
nextor_w(Xp,[X|Xs],[K|Fin],FinOut,XpOut) :-
assertion(Xp+1 =:= X), % The input list is assumed to increase monotonously.
Kn #= K+1, % Next K is constrained to be previous K + 1,
Fin = [Kn|NewFin], % The Fin of the open list is set to a new list cell, with a new Fin
nextor_w(X,Xs,[Kn|NewFin],FinOut,XpOut).
% ---
% Testing
% ---
:- begin_tests(nextor).
test("empty list" ,true(R == [])) :-
nextor([],R).
test("1-elem list",true(R == [2])) :-
nextor([1],R).
test("2-elem list",true(R == [3,4])) :-
nextor([1,2],R).
test("3-elem list",true(R == [4,5,6])) :-
nextor([1,2,3],R).
:- end_tests(nextor).
And so:
?- run_tests.
% PL-Unit: nextor .... done
% All 4 tests passed
true.
How about doing:
next(In,Out) :-
length(In,N),
maplist(plus(N),In,Out).
Uses length/2 and maplist/3. This works for the examples in your question - next([1,2,3,4],R). and next([11,12,13],R). - but only because the lists contain consecutive numbers. next([23,2,18],R). will unify R with [26,5,21].
Or:
next(In,Out) :-
length(In,N),
last(In,LastValue),
MinValue is LastValue+1,
MaxValue is LastValue+N,
numlist(MinValue,MaxValue,Out).
Uses last/2 and numlist/3. With this approach next([23,2,18],R). will unify R with [19,20,21].
This works fine for me:
next(Xs,Ys) :-
next(Xs,[_],Ys).
next([_],[],[]).
next([X],[_|Q],[X1|R]) :-
X1 is X + 1,
next([X1],Q,R).
next([_|T],Q,R) :-
next(T,[_|Q],R).
As it runs down the list it is building up a second list. When it finds the end of the first list it then runs down the second list building the output.
I got this kind of output:
?- next([1,2,3,7,8],W).
W = [9, 10, 11, 12, 13] .

Change list of variables according to another list containing the index and atoms in prolog

I have a list of variables E and a list L and I want a predicate that works like this:
E=[A,B,C,D]
L=[(1,b),(3,m)]
solve(E,L).
E=[b,B,m,D]
Basically solve() should run through the list L and change E by using (a,b) to unify the variable at index a with the atom B. Is there any way to do this?
The meaning of the (badly named) solve/2 predicate is something like "for every pair (Index, Element), the Index-th element of the input list is Element". You are likely using a Prolog implementation that already has a predicate called something like nth1/3 which expresses "the Index-th element of List is Element". For example, in SWI-Prolog:
?- List = [A, B, C, D], nth1(3, List, this_is_the_third_element).
List = [A, B, this_is_the_third_element, D],
C = this_is_the_third_element.
So an alternative implementation of your predicate simply calls nth1/3 for each of your (Index, Element) pairs:
solve(_List, []).
solve(List, [(Index, Elem) | Pairs]) :-
nth1(Index, List, Elem),
solve(List, Pairs).
And with this you're done:
?- E = [A, B, C, D], L = [(1, b), (3, m)], solve(E, L).
E = [b, B, m, D],
A = b,
C = m,
L = [(1, b), (3, m)] ;
false.
Note that this solution is simple, but it has quadratic complexity in the length of the input list: nth1/3 might have to visit the entire N-element list N times. In the unlikely case that you need this predicate for a performance-critical part of some larger program, consider the more optimized solution sketched in the other answer.
Is there any way to do this?
Certainly. And as they say in Perl: "There is more than one way to do it".
Couple of problems:
Do not use (1,b). Use the idiomatic -(1,b) instead, which is written as 1-b (the pair). This gives you a list of pairs: L=[1-b,3-m]. There is a library specifically dealing with such pairs: https://www.swi-prolog.org/pldoc/man?section=pairs - alternatively you can use real maps implemented with AVL trees: https://www.swi-prolog.org/pldoc/man?section=assoc
Now you just need to:
sort the list of pairs, probably using keysort: https://www.swi-prolog.org/pldoc/doc_for?object=sort/2 or https://www.swi-prolog.org/pldoc/doc_for?object=sort/4
Go through the list left to right, keeping the current index, and performing a replacement when the next key in your sorted list is hit, or just retaining the existing term from the list otherwise. The result goes into an accumulator variable as head of a list.
Done! Special handling of out-of-bounds indexes etc. to be suitably handled by throwing or failing.
How to go through the sorted list of pairs (I didn not test this!):
% case of Index hit:
go_through([Index-Value|Rest],Index,InList,OutList) :-
InList = [I|Rest],
OutList = [Value|More],
succ(Index,NextIndex),
go_through(Rest,NextIndex,Rest,More).
% case of Index miss:
go_through([NotYetIndex-Value|Rest],Index,InList,OutList) :-
NotYetIndex > Index, % that should be the case
InList = [I|Rest],
OutList = [I|More],
succ(Index,NextIndex),
go_through(Rest,NextIndex,Rest,More).
go_through([],_,L,L). % DONE
Alternatively, you can write a replace0 that replaces-by-index in a list, and go through the L list.
Addendum: Working code using go_through
Actually contains a few subtlties
another_vectorial_replace1(ListIn,ReplacePairs,ListOut) :-
maplist([_,_]>>true,ListIn,ListOut), % Bonus code: This "makes sure" (i.e. fails if not)
% that ListIn and ListOut are the same length
maplist([(A,B),A-B]>>true,ReplacePairs,RealPairs), % Transform all (1,b) into [1,b]
maplist([K-_]>>integer(K),RealPairs), % Make sure the RealPairs all have integers on first place
keysort(RealPairs,RealPairsSorted), % Sorting by key, which are integers; dups are not removed!
debug(topic,"ListIn: ~q",[ListIn]),
debug(topic,"RealPairsSorted: ~q",[RealPairsSorted]),
go_through(RealPairsSorted,1,ListIn,ListOut),
debug(topic,"ListOut: ~q",[ListOut]).
% Case of Index hit, CurIndex is found in the first "Replacement Pair"
go_through([CurIndex-Value|RestPairs],CurIndex,ListIn,ListOut) :-
!, % Commit to choice
ListIn = [_|Rest],
ListOut = [Value|More],
succ(CurIndex,NextIndex),
go_through(RestPairs,NextIndex,Rest,More).
% Case of Index miss:
go_through([NotYetIndex-V|RestPairs],CurIndex,ListIn,ListOut) :-
NotYetIndex > CurIndex, % that should be the case because of sorting; fail if not
!, % Commit to choice
ListIn = [X|Rest],
ListOut = [X|More],
succ(CurIndex,NextIndex),
go_through([NotYetIndex-V|RestPairs],NextIndex,Rest,More).
% Case of DONE with list traversal
% Only succeed if there are not more pairs left (i.e. no out-of-bound replacements)
go_through([],_CurIndex,L,L).
% ===
% Tests
% ===
:- begin_tests(another_vectorial_replace1).
test(empty) :- another_vectorial_replace1([],[],LO),
LO=[].
test(nop_op) :- another_vectorial_replace1([a,b,c,d],[],LO),
LO=[a,b,c,d].
test(one) :- another_vectorial_replace1([a],[(1,xxx)],LO),
LO=[xxx].
test(two) :- another_vectorial_replace1([a,b,c,d],[(4,y),(2,x)],LO),
LO=[a,x,c,y].
test(full) :- another_vectorial_replace1([a,b,c,d],[(1,e),(2,f),(3,g),(4,h)],LO),
LO=[e,f,g,h].
test(duplicate_replacement,[fail]) :- another_vectorial_replace1([a],[(1,x),(1,y)],_).
test(out_of_bounds_high,[fail]) :- another_vectorial_replace1([a],[(2,y)],_).
test(out_of_bounds_low,[fail]) :- another_vectorial_replace1([a],[(0,y)],_).
:- end_tests(another_vectorial_replace1).
rt :- debug(topic),run_tests(another_vectorial_replace1).
Addendum 2
Replacement using maplist/N, foldl/N and library(assoc)
Recursive calls disappear behind the curtain!
https://github.com/dtonhofer/prolog_notes/blob/master/code/vector_replace0.pl
(the following assumes that the indices in the pairs list will be sorted, in increasing order, as the example in the question indicates.)
What you said can be written as one conjunction
E=[A,B,C,D], L=[(1,a),(3,c)], solve(E,L), E=[a,B,c,D].
which you intend to be holding under the proper definition of solve/2 that you seek to find. But isn't it like saying
E=[A|E2], L=[(1,a)|L2],
E2=[B,C,D], L2=[(3,c)],
solve(E2,L2), E2=[B,c,D],
E=[a|E2].
? Although, something doesn't quite fit right, here. c in E2 appears in second position, not 3rd as indicated by its entry in L2.
But naturally, L2 must be indexed from 2, since it is a tail of L which is indexed from 1. So we must make this explicit:
E=[A,B,C,D], L=[(1,a),(3,c)], solve(E,L), E=[a,B,c,D]
==
E=[A,B,C,D], L=[(1,a),(3,c)], solve(E,1,L), E=[a,B,c,D] % starting index 1
==
E=[A|E2], L=[(1,a)|L2],
E2=[B,C,D], L2=[(3,c)],
solve(E2,2,L2), E2=[B,c,D], E=[a|E2]
must, and now can, hold. But where did a get from, in E? What we actually mean here is
E=[A|E2], L=[(1,a)|L2],
p( (1,a), 1, a), % index match
E2=[B,C,D], L2=[(3,c)],
solve(E2,2,L2), E2=[B,c,D], % starting index 2
E=[a|E2]
with p/3 defined as
p( (I,A), I, A).
And so it must also hold that
E2=[B|E3], L2=[(3,c)],
\+ p( (3,c), 2, c), % index mismatch
E3=[C,D], L3=L2,
solve(E3,3,L3), E3=[c,D], E2=[B|E3]
L2 is not traversed along at this step (L3=L2), since p( (3,c), 2, c) does not hold.
Do you see how the recursive definition of solve/3 reveals itself here? Could you finish it up?

Possible list permutation using a given formula

I am trying to get my head wrap around lists in Prolog. To do this I am trying to create a sort of game. You pass in a list of numbers 1-9 that can be repeated, the list can be any length. The rules are that starting from the first element(e) you can only move to e+2 or e+3 until you get to the end. The goal is to "land" on the highest numbers. In essence it is kind of like hopscotch. The problem I am running into is determining all the possible permutation for paths. So far I have the following.
paths([], []). %empty list returns empty list
paths([X], [X]). %list with one element returns that one element
paths([X1, X2], [X1]). %list with 2 elements returns the first element
paths([X1, X2, X3], [X1,X3]). %list with three elements returns the first and third element
paths() :- % the recursive case for a list with 4+ elements
An list to use would be: [1,2,3,4,5,6,8,7,9,3,6,5,7,8,9]
I need to determine all possible paths using the rule mentioned about. I wish lists could be indexed in Prolog :(
Any logic guidance would be appreciated.
The requirements aren't completely clear, but it seems that:
The second argument is required to have the same first element as the
first argument (you "hop" on the first "square" first always, using
your hopscotch metaphore)
You aren't requiring that the last element of the first list be the
last element of the second list (you aren't requiring that you "land
on" the last "square").
An empty list succeeds with an empty list result (rather than just failing on an empty list - which is another valid approach).
Then this could be implemented as follows. You do not need many explicit 2- and 3-element list cases since they are handled by the recursive clause and simpler base cases.
path([], []).
path([X], [X]).
path([X,_|T], [X|R]) :- % hop over 1 element
path(T, R).
path([X,_,_|T], [X|R]) :- % hop over 2 elements
path(T, R).
For a simple example:
| ?- path([1,2,3,4,5,6], R).
R = [1,3,5] ? ;
R = [1,3,6] ? ;
R = [1,4,6] ? ;
R = [1,4]
yes
If I don't have your requirements exactly right, you should be able to adjust this to suit your needs as it shows how to handle a recursive case. It also sounds like you are headed in the direction of trying to optimize the values in your hops, which I shall also leave as an exercise.
This can also be done with a DCG (definite clause grammar)
path([]) --> [].
path([X]) --> [X].
path([X|T]) --> ([X,_] | [X,_,_]), path(T).
Which would be exercised:
| ?- phrase(path(R), [1,2,3,4,5,6]).
R = [1,3,5] ? ;
R = [1,3,6] ? ;
R = [1,4,6] ? ;
R = [1,4] ? ;
(1 ms) no
| ?-
In light of the extra requirement that the last step taken must be one that falls within the list, here is an updated version of the path/2 predicate:
path([], []).
path([X], [X]).
path([X,_], [X]).
path([X,_,Y|T], [X|R]) :- % hop over 1 element
path([Y|T], R).
path([X,_,_,Y|T], [X|R]) :- % hop over 2 elements
path([Y|T], R).
I think that there is a reason to avoid indexing: simplicity. If you decompose your problem, maybe you could start writing a step/3 predicate like
step([_,X|T],X,T).
step([_,_,X|T],X,T).
and then
paths([],[]).
paths(L,[X|Xs]) :- step(L,X,T), paths(T,Xs).
note: I don't understand very well your game, some example of playground and solution would be welcome.
%passing in a list and return all possible paths using K+2 or K+3 with K being the first element of the list.
%empty list returns empty list
%list with one element returns that one element
%list with 2 elements returns the first element
%list with three elements returns the first and third element
%list with four/four+ elements needs to be called recursively, prefix them with the first element and append them together
%RL means ReturnList
%FL means FinalList
%List is the appended list containing all the paths
paths([], []).
paths([X], [[X]]).
paths([X1, X2], [[X1]]).
paths([X1, X2, X3], [[X1,X3]]).
paths([X1, X2, X3, X4 | T], List) :-
paths([X3,X4|T], RL), paths([X4|T], RL2),
prefix_all(X1, RL, FL1), prefix_all(X1, RL2, FL2),
append(FL1, FL2, List).
So if run with the list [1,2,3,4,5] is would produce the following:
| ?- paths([1,2,3,4,5],X).
X = [[1,3,5],[1,4]] ? ;
no

Leave only one copy of the repeated elements

I'm trying to create a predicate in Prolog that takes a list and returns only one copy of the adjacent duplicates of the list.
for example:
?- adj_dups([a,b,a,a,a,c,c],R).
R=[a,c]
I think I need two base cases:
adj_dups([],[]). % if list is empty, return empty list
adj_dups([X],[]). % if list contains only one element, return empty list (no duplicates).
then for the recursive part, I need to compare the head with the head of the tail, and then go recursively on the tail of the list.
This is what I came up with so far, but it doesn't work!
adj_dups([X,X|T],[X|R]):- adj_dups([X|T],R). % if the list starts with duplicates
adj_dups([X,Y|T],R):- X \= Y, adj_dups([X|T],R). % if the list doesn't start wih duplicates
How can I fix it so I can get the right result?
Edit:
I'll list some examples to help you all understand my problem.
How the code supposed to behave:
?- adj_dups([a,c,c,c,b],R).
R = [c]
?- adj_dups([a,b,b,a,a],R).
R = [b,a]
?- adj_dups([a,b,b,a],R).
R = [b]
How my code is behaving:
?- adj_dups([a,c,c,c,b],R).
R = []
?- adj_dups([a,b,b,a,a],R).
R = [a,a]
?- adj_dups([a,b,b,a],R).
R = [a]
Thank you.
I find ambiguous this specification
only one copy of the adjacent duplicates of the list
as it doesn't clarify what happens when we have multiple occurrences of the same duplicate symbol.
adj_dups([],[]).
adj_dups([X,X|T],[X|R]) :-
skip(X,T,S),
adj_dups(S,R),
\+ memberchk(X,R),
!.
adj_dups([_|T],R) :- adj_dups(T,R).
skip(X,[X|T],S) :- !, skip(X,T,S).
skip(_,T,T).
This yields
?- adj_dups([a,a,c,c,a,a],R).
R = [c, a].
Comment the + memberchk line to get instead
?- adj_dups([a,a,c,c,a,a],R).
R = [a, c, a].
Let's look at what happens when you try a simpler case:
adj_dups([a,b,b,a],R).
The first three predicates don't match, so we get:
adj_dups([X,Y|T],R):- X \= Y, adj_dups([X|T],R).
This is the problematic case: X is bound to a, Y is bound to b.
It will then call adj_dups([a,b,a],R), binding T to [b,a], which only has a single b. Effectively, you have now removed the duplicate b from the list before it could be processed.
Let's create a few auxiliary predicates first - especially a predicate that filters an element from a list. Then, in the recursive part, there are two cases:
If the first element occurs in the tail of the list being processed, it is duplicated; we need to return that first element followed by the processed tail. Processing the tail consists of removing that first element from it, then check the tail for duplicates.
The second case is much simpler: if the first element does not occur in the tail, we simply apply adj_dups to the tail and return that. The first element was never duplicated, so we forget about it.
% Filter the element X from a list.
filter(X,[],[]).
filter(X,[X|T],R) :- filter(X,T,R).
filter(X,[Y|T],[Y|R]) :- X \= Y, filter(X,T,R).
% Return "true" if H is NOT a member of the list.
not_member(H,[]).
not_member(H,[H|T]):-fail.
not_member(H,[Y|T]):-H \= Y, not_member(H,T).
% Base cases for finding duplicated values.
adj_dups([],[]). % if list is empty, return empty list
adj_dups([X],[]). % if list contains only one element, return empty list (no duplicates).
% if H1 is in T1 then return the H1 followed by the adj_dups of (T1 minus H1).
% if H1 is not in T1 then return the adj_dups of T1.
adj_dups([H1|T1],[H1|T3]):-member(H1,T1), filter(H1,T1,T2), adj_dups(T2,T3).
adj_dups([H1|T1],T3):-not_member(H1, T1), adj_dups(T1,T3).
This gives R=[a,b] for the input [a,b,b,a], and R=[a,c] for your example input [a,b,a,a,a,c,c].

How do I remove supersets in a list of lists?

Let's say I have the following list:
List = [[a],[a,b],[a,c],[b,c],[b,d],[a,b,c],[a,b,d],[b,c,e],[b,d,e,f]]
The goal is to remove every list in the list that is a superset of a list in the list.
The list that contains the lists always has the following properties:
The lists in the list are sorted by length
Each list in the list is sorted
My initial idea was to simply start with the first list in the list and go through all other lists and remove the lists that are a superset. Next I'd look at the second list, et cetera.
After removing all supersets of the list [a] it should look like this:
List = [[a],[b,c],[b,d],[b,c,e],[b,d,e,f]]
Next the supersets of [b,c] should be removed:
List = [[a],[b,c],[b,d],[b,d,e,f]]
Last is the supersets of [b,d]:
List = [[a],[b,c],[b,d]]
And the line above should be the result.
I already made a predicate akin to the member predicate, but instead of taking a single element and comparing it to the list, this takes an entire list and compares it to the list:
memberList([],_).
memberList([X|Xs],Y) :-
member(X,Y),
memberList(Xs,Y).
This only works with lists.
?- memberList(a,[a,b,c]).
false.
?- memberList([a],[a,b,c]).
true .
?- memberList([a,b],[a,b,c]).
true .
But after this I'm a bit lost.
I tried the following which should remove the supersets of a single set, but it did not work:
removeSupersetsList(_,[],[]).
removeSupersetsList(X,[Y|Ys],[Y|Out]) :-
not(memberList(X,Y)),
removeSupersetsList(X,Ys,Out).
removeSupersetsList(X,[Y|Ys],Out) :-
memberList(X,Y),
removeSupersetsList(X,Ys,Out).
So I was wondering if someone could point me in the right direction to remove all supersets from a list or maybe even give the right predicate.
I'm using SWI-Prolog, where I find a crafted libray for ordered sets, and the required test, then using select/3 it's really easy to sanitize the list
rem_super_sets([], []).
rem_super_sets([L|Ls], R) :-
( select(T, Ls, L1), % get any T in Ls
ord_subset(L, T) % is T a superset of L ?
-> rem_super_sets([L|L1], R) % discard T, keep L for further tests
; R = [L|L2],
rem_super_sets(Ls, L2)
).
here a verification and the result
test :-
List = [[a],[a,b],[a,c],[b,c],[b,d],[a,b,c],[a,b,d],[b,c,e],[b,d,e,f]],
rem_super_sets(List, R),
write(R).
?- test.
[[a],[b,c],[b,d]]
true.
memberList([],_).
memberList([X|Xs],Y) :- member(X,Y),
memberList(Xs,Y).
%remove(ToRemove,ListWithSublists,LocRez,FinalRez)
%A list from ListWithSublists is removed,depending on ToRemove
% LocRez is accumulator used to obtain the FinalRez ( at the end )
remove(_,[],LocRez,LocRez) :- !.
remove(ToRemove,ListWithSublists,LocRez,FinalRez) :- ListWithSublists=[Sublist|Rest],
memberList(ToRemove,Sublist),
remove(ToRemove,Rest,LocRez,FinalRez),!.
remove(ToRemove,ListWithSublists,LocRez,FinalRez) :- ListWithSublists=[Sublist|Rest],
not(memberList(ToRemove,Sublist)),
append(LocRez,[Sublist],LocRezNew),
remove(ToRemove,Rest,LocRezNew,FinalRez),!.
> removeSupersetsList(List,Rez) :- removeSupersetsList(List,[],Rez). % call this for testing
%removeSupersetsList(List,LocRez,Final)
%remove the Head from List from the List itself if needed(obtain Rez in the process)
%append the Head into our LocRez(get LocRezNew),
%call this recursively for the Rez
removeSupersetsList(List,LocRez,LocRez) :- List=[] ,!.
removeSupersetsList(List,LocRez,Final) :- ( List=[ToRemove|_] ; List=[ToRemove] ),
remove(ToRemove,List,[],Rez),
append(LocRez,[ToRemove],LocRezNew),
removeSupersetsList(Rez,LocRezNew,Final),!.