Check if list is ordered - list

I'm trying to compare the elements of a list of integer to see if they are ordered (or not). I'm using Amzi!
I gave a few attempts, but nothing works... :(
ordered([X]).
ordered([N|[N1|L]]) :- N <= N1, ordered([N1|L]).
ordered_([X]).
ordered_([Head,Head1|Tail]) :- Head <= Head1, ordered_([Head1|Tail]).
Both return no if this list is entered:
ordered([1,2,3,4]).
ordered_([1,2,3,4]).
I understand that I need to compare the head with the head of the tail.

Doesn't seem like it should be any more complex than
ordered( [] ) .
ordered( [_] ) .
ordered( [X,Y|Z] ) :- X =< Y , ordered( [Y|Z] ) .
Arithmetic comparison predicates are covered here: http://www.amzi.com/manuals/amzi/pro/ref_math.htm#MathematicalComparisons
Use #=</2 or compare/3 to check the ordering of things in the standard order of terms: http://www.amzi.com/manuals/amzi/pro/ref_manipulating_terms.htm#StandardOrder

a compact alternative:
ordered(L) :- \+ ( append(_,[A,B|_], L), A > B ).

More efficient alternative to most upvoted solution, comparing three instead of appending the bigger element back to the list
is_sorted([]).
is_sorted([X, Y, Z|T]) :- X =< Y, Y =< Z, is_sorted(T).
is_sorted([X, Y|T]) :- X =< Y, is_sorted(T).

Related

How to construct pair of items on two lists using recursion in prolog

Hie, I am a newbie in Prolog, especially recursion in Prolog. Here, start recursive on list X, makepairs recursive on list Y. These two rules should make a list of the pairs of items on X and Y. For example, if I enter query:
?- start([a,b], [c,d], Z)
Prolog should print out:
Z = [pair(a,c), pair(a,d), pair(b,c), pair(b,d)].
But my code prints only false. Could anyone help to find the bug in my code?
start([H|T], Y, Z):- makepairs(H, Y, Z), start(T, Y, Z).
start([], _Y, []).
makepairs(X, [H|T], Z) :- append([pair(X,H)], [], Z), makepairs(X, T, Z).
makepairs(_X, [], _Z).
Using library(lamdba) preinstalled in Scryer, available for
SICStus|SWI.
start(Xs, Ys, XYs) :-
maplist(\X^Y^pair(X,Y)^true, Xs, Ys, XYs).
Or manually,
list_list_pairs([], [], []).
list_list_pairs([X|Xs], [Y|Ys], [pair(X,Y)|Pairs]) :-
list_list_pairs(Xs, Ys, Pairs).
Note that this not only constructs such pairs, but it can also be used to "unzip" them:
?- list_list_pairs(Xs, Ys, [pair(1,one), pair(2,two), pair(3,three)]).
Xs = [1,2,3], Ys = [one,two,three].
But, maybe I should add, using pair/2 as a functor is fairly uncommon. It is more idiomatic in Prolog to use (-)/2 instead, which is so much more compact, think of
Ps = [1-one,2-two,3-three].
% vs
Ps = [pair(1,one), pair(2,two), pair(3,three)]
Assuming that this is a learning exercise, you are supposed to roll your own...
For the purposes of this exercise, I'm going to elect to represent the tuple using the :/2 operator (x:y), simply because it's less typing, more compact, and and easier on the eyes than, say, [x,y].
So, there are 3 cases in this problem:
Both lists are the empty list. The result is the empty list. You can represent that as
zip( [] , [] , [] ) .
Both lists are non-empty lists. The result is that we prepend the pair to the result list, and continue, thus:
zip( [X|Xs] , [Y|Ys] , [X:Y|Zs] ) :- zip(Xs,Ys,Zs) .
And then, there is the case where one list is empty and the other is non-empty. You need to consider how to handle that situation. You could
Fail.
Terminate the program and succeed, discarding the unmatched items.
Include the unpaired item as itself.
Include the unpaired item in the same x:y pair structure, selecting some atom to represent the missing data.
Here, I choose to include the last option, and will represent the missing data with the atom nil, so [nil:y] or [x:nil].
You can represent this in Prolog as
zip( [] , [Y|Ys] , [nil:Y|Zs] ) :- zip([],Ys,Zs) .
zip( [X|Xs] , [] , [X:nil|Zs] ) :- zip(Xs,[],Zs) .
Putting it all together, you get this:
zip( [] , [] , [] ) .
zip( [] , [Y|Ys] , [nil:Y|Zs] ) :- zip([],Ys,Zs) .
zip( [X|Xs] , [] , [X:nil|Zs] ) :- zip(Xs,[],Zs) .
zip( [X|Xs] , [Y|Ys] , [X:Y|Zs] ) :- zip(Xs,Ys,Zs) .
which you can fiddle with at https://swish.swi-prolog.org/p/zip/unzip.pl
Running
zip( [a,b,c], [1,2,3], Ps ).
results in
P = [ a:1, b:2, c:3 ]
You might note that this will also unzip a list of tuples, so running
zip(Xs,Ys,[a:1,b:2,c:3]).
results in
Xs = [a,b,c]
Ys = [1,2,3]
This line cannot succeed:
start([H|T],Y,Z):- makepairs(H,Y,Z), start(T,Y,Z).
The first part requires Prolog to find a value for Z which is the list of all pairs, the second part requires Z to become only the list of H paired with every element in Y, and the third part requires Z to become the pairs of the tail and Y.
One single Z cannot be three different things at the same time, the predicate cannot hold, and false must be the result.
This line:
start([],_Y,[]).
Introduces a helper variable, which you never use.
This line:
makepairs(X,[H|T],Z):-append([pair(X,H)],[], Z), makepairs(X,T,Z).
requires that Z is the list of pairs of X with everything in [H|T], and also that Z is what you get when you append an empty list onto a list with one pair, and that Z is the list of pairs of X with T. This has the same problem of requiring Z to be three different things. These lines are where you need to introduce helper variables such as Z_.
Flaws in the predicate makepairs/3
In the base case, makepairs(_X, [], _Z), the variable _Z remains free, but it should be instantiated to [].
In the recursive case, append([pair(X, H), [], Z] is equivalent to Z = [pair(X, H)] (however, all you need is Z = pair(X,H)); also, the recursive call must produce a list containing the remaining pairs, say Zs. So the final result should be [Z|Zs].
Thus, a correct code is:
makepairs(_X, [], []).
makepairs(X, [H|T], [Z|Zs]):-
Z = pair(X,H),
makepairs(X, T, Zs).
Example:
?- makepairs(a, [c,d], Pairs).
Pairs = [pair(a, c), pair(a, d)] ;
false. % <= spurious choice point!
Flaws in predicate start/3
In the recursive case, subgoal makepairs(H, Y, Z) produces a list Z containing only pairs whose first elements are equal to H; then, the recursive call must produce a list Zs containing the remaining pairs. So, the final result, say Zss, must be the concatenation of lists Z and Zs.
Thus, a correct code is:
start([], _Y, []).
start([H|T], Y, Zss):-
makepairs(H, Y, Z),
append(Z, Zs, Zss),
start(T, Y, Zs).
Example:
?- start([a,b], [c,d], Z).
Z = [pair(a, c), pair(a, d), pair(b, c), pair(b, d)] ;
false. % <= spurious choice point
A BETTER SOLUTION
A better solution, that avoid spurious choice point using first argument indexing, is:
make_pairs([], _, []).
make_pairs([X|Xs], Y, Pairs):-
make_pairs_helper(Y, X, Px),
append(Px, Pxs, Pairs),
make_pairs(Xs, Y, Pxs).
make_pairs_helper([], _, []).
make_pairs_helper([Y|Ys], X, [pair(X,Y)|Zs]):-
make_pairs_helper(Ys, X, Zs).
Example:
?- make_pairs([a,b], [c,d], Pairs).
Pairs = [pair(a, c), pair(a, d), pair(b, c), pair(b, d)].
Remark It's more idiomatic to use - as separator of the elements of a pair in Prolog.

Subtracting or adding lists of lists in prolog?

I am fairly new to prolog and am trying to mess around with lists of lists. I am curious on how to add two lists of lists or subtract them resulting in one list of list. If I have two lists of lists lets say,
SomeList = [[1,2,3,4],[5,6,7,8]]
SomeList2 = [[1,2,3,4],[5,6,7,8]]
How could I add or subtract SomeList and SomeList2 to create a list of lists? Resulting in a sum of say
sumList([[2,4,6,8],[10,12,14,16]])
or vice-versa for subtraction? Any help would be appreciated not looking for code but for insight !
The easiest approach is with maplist:
add(X, Y, Z) :- Z is X + Y.
op_lists(L1, L2, R) :-
maplist(maplist(add), L1, L2, R).
Which gives:
| ?- op_lists([[1,2,3,4],[5,6,7,8]], [[1,2,3,4],[5,6,7,8]], R).
R = [[2,4,6,8],[10,12,14,16]]
yes
| ?-
In the expression:
maplist(maplist(add), L1, L2, R).
maplist(G, L1, L2, R) calls G on each element of L1 and L2, resulting in each element of R. Since each element of L1 and L2 is a list, then G in this case is maplist(add) which calls add on each element of the sublists.
You can obviously modify add(X, Y, Z) to be whatever operation you wish on each pair of elements. You can also make the addition more "relational" by using CLP(FD):
add(X, Y, Z) :- Z #= X + Y.
Then you also get, for example:
| ?- op_lists([[1,2,3,4],[5,6,7,8]], L, [[3,6,9,12],[10,12,14,16]]).
L = [[2,4,6,8],[5,6,7,8]]
yes
| ?-
If you wanted to do this without maplist, you could still use add/3 and use a two-layer approach:
op_lists([], [], []).
op_lists([LX|LXs], [LY|LYs], [LR|LRs]) :-
op_elements(LX, LY, LR),
op_lists(LXs, LYs, LRs).
op_elements([], [], []).
op_elements([X|Xs], [Y|Ys], [R|Rs]) :-
add(X, Y, R),
op_elements(Xs, Ys, Rs).
You can see the simple list processing pattern here, which the use of maplist takes care of for you.
Besides the solutions presented by #lurker (+1), I would also add the possibility to use DCGs, since you are working on lists. For the available operations I suggest to define a slightly more general predicate opfd/4 instead of add/3. Here are exemplary rules for addition and subtraction as asked in your question, you can use these as templates to add other two-place arithmetic operations:
opfd(+,X,Y,Z) :-
Z #= X+Y.
opfd(-,X,Y,Z) :-
Z #= X-Y.
As the desired operation is an argument, you only need one DCG-rule to cover all operations (marked as (1) at the corresponding goal). This way, of course, you have to specify the desired operation as an argument in your relation and pass it on to the DCGs. The structure of these DCGs is very similar to the last solution presented by #lurker, except that the resulting list does not appear as an argument since that is what the DCGs describe. For easier comparison I will stick with the names op_lists//3 and op_elements//3, the calling predicate shall be called lists_op_results/4:
lists_op_results(L1,L2,Op,Rs) :-
phrase(op_lists(Op,L1,L2),Rs).
op_lists(_Op,[],[]) -->
[].
op_lists(Op,[X|Xs],[Y|Ys]) -->
{phrase(op_elements(Op,X,Y),Rs)},
[Rs],
op_lists(Op,Xs,Ys).
op_elements(_Op,[],[]) -->
[].
op_elements(Op,[X|Xs],[Y|Ys]) -->
{opfd(Op,X,Y,R)}, % <-(1)
[R],
op_elements(Op,Xs,Ys).
Example queries:
?- lists_op_results([[1,2,3,4],[5,6,7,8]], [[1,2,3,4],[5,6,7,8]], +, R).
R = [[2,4,6,8],[10,12,14,16]]
?- lists_op_results([[1,2,3,4],[5,6,7,8]], [[1,2,3,4],[5,6,7,8]], -, R).
R = [[0,0,0,0],[0,0,0,0]]
#lurker's example:
?- lists_op_results([[1,2,3,4],[5,6,7,8]], L, +, [[3,6,9,12],[10,12,14,16]]).
L = [[2,4,6,8],[5,6,7,8]]
You can also ask if there is an operation that fits the given lists:
?- lists_op_results([[1,2,3,4],[5,6,7,8]], L, Op, [[3,6,9,12],[10,12,14,16]]).
L = [[2,4,6,8],[5,6,7,8]],
Op = + ? ;
L = [[-2,-4,-6,-8],[-5,-6,-7,-8]],
Op = -
On a sidenote: Since the operation is the first argument of opfd/4 you can also use it with maplist as suggested in #lurker's first solution. You just have to pass it lacking the last three arguments:
?- maplist(maplist(opfd(Op)),[[1,2,3,4],[5,6,7,8]], L, [[3,6,9,12],[10,12,14,16]]).
L = [[2,4,6,8],[5,6,7,8]],
Op = + ? ;
L = [[-2,-4,-6,-8],[-5,-6,-7,-8]],
Op = -

Prolog, X before Y in a List

I am having trouble understanding prolog, I have to find if X is before Y in a list.
so I have a base case with an empty list
before(X, Y, [ ]).
Now I know that I want to check the index of X and the index of Y in List and if indexX < indexY I want to have a success.
Could someone explain a simple way to do this?
You can use append/3 to locate X and the remaining list after it, then locate Y.
before(X, Y, L):-
append(_, [X|Tail], L),
append(_, [Y|_], Tail).
Using a DCG, it would look like this (using a predicate named ... for notational/visual convenience):
before(X, Y) --> ..., [X], ..., [Y], ... .
... --> [].
... --> [_], ... .
| ?- phrase(before(X, Y), [a,b,c]).
X = a
Y = b ? ;
X = a
Y = c ? ;
X = b
Y = c ? ;
(1 ms) no
And you can wrap it in a predicate, if you wish:
before(X, Y, L) :- phrase(before(X, Y), L).
As #CapelliC points out, the above predicate succeeds if there is at least one case in the list in which X comes before Y. However, if the definition is, X is seen before Y in the list, then an alternative DCG implementation could be:
before(X, Y) --> anything_but(Y), [X], ..., [Y], ... .
anything_but(_) --> [].
anything_but(Y) --> [X], { dif(X, Y) }, anything_but(Y).
... --> [].
... --> [_], ... .
Which results in:
| ?- phrase(before(X,Y), [b,a,b]).
X = b
Y = b ? a
X = a
Y = b
no
In Prolog, list processing is in most cases done without using indices: you use recursion, and you try to formulate it as a logical expression. If you don't want to use built-ins, you can write:
before(X,Y,[X|T]) :-
!,
contains(Y,T).
before(X,Y,[_|T]) :-
before(X,Y,T).
contains(Y,[Y|_]) :-
!.
contains(Y,[_|T]) :-
contains(Y,T).
The code makes use of a defined contains/2 predicate that checks whether the list L contains Y. Now the before/2 predicate contains two clauses. The first clause specifies that the first element of the list is X, in that case, we only need to check whether the remainder of the list contains an Y. In case the first element of the list is not an X, the list is shifted one further, and by using recursion, we try to find a location where there is an X.
Note that this predicate requires that both X and Y are elements of the list. Furthermore there can be multiple X and Ys. So before(a,b,[b,a,a,b]) will succeed, simple because there is an a and a b such that the a is before the b.
EDIT
If you want to use the predicate in a reversed way (query fashion), you should omit the cuts:
before(X,Y,[X|T]) :-
contains(Y,T).
before(X,Y,[_|T]) :-
before(X,Y,T).
contains(Y,[Y|_]).
contains(Y,[_|T]) :-
contains(Y,T).
Then you can query like:
?- before(X,Y,[a,b,c]).
X = a,
Y = b ;
X = a,
Y = c ;
X = b,
Y = c ;
false.
Here's a simple solution that uses no built-in predicates whatsoever.
It helps if you re-cast the problem in somewhat more generic terms.
A common prolog idiom is a public predicate that invokes a worker predicate that does all the work. Often, the worker predicate will carry additional variable that maintain state. In this case, we don't need to maintain state, but it simplifies things if we make the actual solution more generic: instead of defining the problem in terms of X and Y, redefineit in terms of a list of arbitrary length, defining the order in which things must be found in the target list.
Then, it's simply a matter of recursing down both lists in parallel to determine if the precedence constraints are satisfied. The generic solution (which will work for a list containing an arbitrary number of constraints) has 3 cases:
The constraint list is empty: Success!
The head of the constraint list unifies with the head of the list being
tested. That indicates that a constraint has been satisfied. Remove both the
constraint and the item it just matched (the head of the list being tested)
and recurse down.
Finally, just remove the head of the list being tested and recurse down.
The solution looks like this:
x_before_y( X , Y, Zs ) :- satisfies_constraints( [X,Y] , Zs ) .
satisfies_constraints( [] , _ ) .
satisfies_constraints( [C|Cs] , [C|Xs] ) :- satisfies_constraints(Cs,Xs) .
satisfies_constraints( Cs , [_|Xs] ) :- satisfies_constraints(Cs,Xs) .
On backtracking, this will find all possible solutions. If that's not desirable, a cut in the 2nd clause will eliminate the choice points:
satisfies_constraints( [] , _ ) .
satisfies_constraints( [C|Cs] , [C|Xs] ) :- !, satisfies_constraints(Cs,Xs) .
satisfies_constraints( Cs , [_|Xs] ) :- satisfies_constraints(Cs,Xs) .
As will introducing a test for non-unifiability in the 3rd clause:
satisfies_constraints( [] , _ ) .
satisfies_constraints( [C|Cs] , [C|Xs] ) :- satisfies_constraints(Cs,Xs) .
satisfies_constraints( [C|Cs] , [X|Xs] ) :-
C \= X ,
satisfies_constraints([C|Cs],Xs)
.

Friendly lists prolog

I am given 2 lists for example K=[a,b,c,d,e,f,g] and L=[a,b,1,d,e,2,g]. When these 2 lists have 2 different elements, then they are friendly.
This is what I've tried:
friendly(K,L):-
append(L1,[Z],A1),
append(A1,L2,A2),
append(A2,[Q],A3),
append(A3,L3,K),
append(L1,[Y],B1),
append(B1,L2,B2),
append(B2,[W],B3),
append(B3,L3,L),
Z\=Y,
Q\=W.
Thank you all so much, at last I found the correct code:
friend(L1,L2):-
append(A,Y,L1),
append([Z|T],[F|TT],Y),
append(A,Q,L2),
append([R|T],[O|TT],Q),
Z\=R,
F\=O.
You can use append/3 in this way to locate the first different elements.
first_different(L1,L2, R1,R2) :-
append(H, [E1|R1], L1),
append(H, [E2|R2], L2),
E1 \= E2.
H is the common part, R1,R2 are the 'remainders'. This code is more in line with your second comment above.
Now you must apply two times this helper predicate, and the second time also 'remainders' must be equal, or one of them must be empty. That is
friendly(L1,L2) :-
first_different(L1,L2,R1,R2),
first_different(R1,R2,T1,T2),
once((T1=T2;T1=[];T2=[])).
Alternatively, using some builtin can be rewarding. This should work
friendly(L1,L2) :- findall(_,(nth1(I,L1,E1),nth1(I,L2,E2),E1\=E2),[_,_]).
Wouldn't it be better to do something like the following?
diff([], [], []).
diff([], K, K).
diff(L, [], L).
diff([H | TL], [H | TK], D) :- diff(TL, TK, D),!.
diff([HL | TL], [HK | TK], [HL, HK | D]) :- diff(TL, TK, D),!.
friendly(K, L) :- diff(K, L, D), length(D, Length), Length < 3.
But your problem really is underspecified. For example my program really cares about order so [a,x,b] and [a,b] are not friendly by my definition.
I'm still a little uncertain about the total definition of "friendly" list, but I think this might answer it:
friendly(A, B) :-
friendly(A, B, 2).
friendly([H|TA], [H|TB], C) :-
C > 0,
friendly(TA, TB, C).
friendly([HA|TA], [HB|TB], C) :-
HA \= HB,
C > 0,
C1 is C-1,
friendly(TA, TB, C1).
friendly(A, [], C) :-
length(A, L),
L =< C.
friendly([], B, C) :-
length(B, L),
L =< C.
friendly(A, A, 0).
I'm assuming that the definition of friendly means the lists are in "lock step" outside of the maximum of two differences.
Does order matter? Are the lists sets (each element is unique) or bags (duplicates allowed)?
Assuming that
Order doesn't matter ([1,2,3] and [1,3,2]) are treated as identical), and
Duplicates don't matter ([1,2,3,1] and [1,2,3]) are treated as identical
Something like this might be along the lines of what you're looking for:
friendly(Xs,Ys) :-
set_of(
E ,
(
( member(E,Xs) ,
not( member(E,Ys) )
)
;
(
member(E,Ys) ,
not( member(E,Xs) )
) ,
Zs
) ,
length( Zs , L ) ,
L =< 2
.
Find the set of all elements of each list that aren't in the other and succeed if the resulting list is of length 0, 1 or 2.
I came up with something similar to others.. I just keep a list of '_' items (final param of diff_list) - one for each difference, be that a value difference at the same index, or a difference in the length, then finally in friendly/2, check that has 2 items.
% recursion base
diff_list([], [], []).
% the head of both lists are the same, don't add to diff list
diff_list([HK|TK], [HK|TL], Diff) :-
diff_list(TK, TL, Diff).
% the above rule failed, so must be a difference, add a '_'
diff_list([_|TK], [_|TL], [_|Diff]) :-
diff_list(TK, TL, Diff).
% 1st list is empty, but the 2nd isn't. That's a diff again.
diff_list([], [_|TL], [_|Diff]) :-
diff_list([], TL, Diff).
% 2nd list is empty, but the 1st isn't. Another diff.
diff_list([_|TK], [], [_|Diff]) :-
diff_list(TK, [], Diff).
% friendly is true if the diff list length unifies with 2 item length list [_,_]
friendly(K, L) :-
diff_list(K, L, [_,_]).

Remove duplicates in list (Prolog)

I am completely new to Prolog and trying some exercises. One of them is:
Write a predicate set(InList,OutList)
which takes as input an arbitrary
list, and returns a list in which each
element of the input list appears only
once.
Here is my solution:
member(X,[X|_]).
member(X,[_|T]) :- member(X,T).
set([],[]).
set([H|T],[H|Out]) :-
not(member(H,T)),
set(T,Out).
set([H|T],Out) :-
member(H,T),
set(T,Out).
I'm not allowed to use any of built-in predicates (It would be better even do not use not/1). The problem is, that set/2 gives multiple same solutions. The more repetitions in the input list, the more solutions will result. What am I doing wrong? Thanks in advance.
You are getting multiple solutions due to Prolog's backtracking. Technically, each solution provided is correct, which is why it is being generated. If you want just one solution to be generated, you are going to have to stop backtracking at some point. This is what the Prolog cut is used for. You might find that reading up on that will help you with this problem.
Update: Right. Your member() predicate is evaluating as true in several different ways if the first variable is in multiple positions in the second variable.
I've used the name mymember() for this predicate, so as not to conflict with GNU Prolog's builtin member() predicate. My knowledge base now looks like this:
mymember(X,[X|_]).
mymember(X,[_|T]) :- mymember(X,T).
not(A) :- \+ call(A).
set([],[]).
set([H|T],[H|Out]) :-
not(mymember(H,T)),
set(T,Out).
set([H|T],Out) :-
mymember(H,T),
set(T,Out).
So, mymember(1, [1, 1, 1]). evaluates as true in three different ways:
| ?- mymember(1, [1, 1, 1]).
true ? a
true
true
no
If you want to have only one answer, you're going to have to use a cut. Changing the first definition of mymember() to this:
mymember(X,[X|_]) :- !.
Solves your problem.
Furthermore, you can avoid not() altogether, if you wish, by defining a notamember() predicate yourself. The choice is yours.
A simpler (and likely faster) solution is to use library predicate sort/2 which remove duplicates in O(n log n). Definitely works in Yap prolog and SWIPL
You are on the right track... Stay pure---it's easy!
Use reified equality predicates =/3 and dif/3 in combination with if_/3, as implemented in Prolog union for A U B U C:
=(X, Y, R) :- X == Y, !, R = true.
=(X, Y, R) :- ?=(X, Y), !, R = false. % syntactically different
=(X, Y, R) :- X \= Y, !, R = false. % semantically different
=(X, Y, R) :- R == true, !, X = Y.
=(X, X, true).
=(X, Y, false) :-
dif(X, Y).
% dif/3 is defined like (=)/3
dif(X, Y, R) :- X == Y, !, R = false.
dif(X, Y, R) :- ?=(X, Y), !, R = true. % syntactically different
dif(X, Y, R) :- X \= Y, !, R = true. % semantically different
dif(X, Y, R) :- R == true, !, X \= Y.
dif(X, Y, true) :- % succeed first!
dif(X, Y).
dif(X, X, false).
if_(C_1, Then_0, Else_0) :-
call(C_1, Truth),
functor(Truth,_,0), % safety check
( Truth == true -> Then_0 ; Truth == false, Else_0 ).
Based on these predicates we build a reified membership predicate list_item_isMember/3. It is semantically equivalent with memberd_truth/3 by #false. We rearrange the argument order so the list is the 1st argument. This enables first-argument indexing which prevents leaving useless choice-points behind as memberd_truth/3 would create.
list_item_isMember([],_,false).
list_item_isMember([X|Xs],E,Truth) :-
if_(E = X, Truth = true, list_item_isMember(Xs,E,Truth)).
list_set([],[]).
list_set([X|Xs],Ys) :-
if_(list_item_isMember(Xs,X), Ys = Ys0, Ys = [X|Ys0]),
list_set(Xs,Ys0).
A simple query shows that all redundant answers have been eliminated and that the goal succeeds without leaving any choice-points behind:
?- list_set([1,2,3,4,1,2,3,4,1,2,3,1,2,1],Xs).
Xs = [4,3,2,1]. % succeeds deterministically
Edit 2015-04-23
I was inspired by #Ludwig's answer of set/2, which goes like this:
set([],[]).
set([H|T],[H|T1]) :- subtract(T,[H],T2), set(T2,T1).
SWI-Prolog's builtin predicate subtract/3 can be non-monotone, which may restrict its use. list_item_subtracted/3 is a monotone variant of it:
list_item_subtracted([],_,[]).
list_item_subtracted([A|As],E,Bs1) :-
if_(dif(A,E), Bs1 = [A|Bs], Bs = Bs1),
list_item_subtracted(As,E,Bs).
list_setB/2 is like set/2, but is based on list_item_subtracted/3---not subtract/3:
list_setB([],[]).
list_setB([X|Xs1],[X|Ys]) :-
list_item_subtracted(Xs1,X,Xs),
list_setB(Xs,Ys).
The following queries compare list_set/2 and list_setB/2:
?- list_set([1,2,3,4,1,2,3,4,1,2,3,1,2,1], Xs).
Xs = [4,3,2,1]. % succeeds deterministically
?- list_setB([1,2,3,4,1,2,3,4,1,2,3,1,2,1],Xs).
Xs = [1,2,3,4]. % succeeds deterministically
?- list_set(Xs,[a,b]).
Xs = [a,b]
; Xs = [a,b,b]
; Xs = [a,b,b,b]
... % does not terminate universally
?- list_setB(Xs,[a,b]).
Xs = [a,b]
; Xs = [a,b,b]
; Xs = [a,b,b,b]
... % does not terminate universally
I think that a better way to do this would be:
set([], []).
set([H|T], [H|T1]) :- subtract(T, [H], T2), set(T2, T1).
So, for example ?- set([1,4,1,1,3,4],S) give you as output:
S = [1, 4, 3]
Adding my answer to this old thread:
notmember(_,[]).
notmember(X,[H|T]):-X\=H,notmember(X,T).
set([],[]).
set([H|T],S):-set(T,S),member(H,S).
set([H|T],[H|S]):-set(T,S),not(member(H,S)).
The only virtue of this solution is that it uses only those predicates that have been introduced by the point where this exercise appears in the original text.
This works without cut, but it needs more lines and another argument.
If I change the [H2|T2] to S on line three, it will produce multiple results. I don't understand why.
setb([],[],_).
setb([H|T],[H|T2],A) :- not(member(H,A)),setb(T,T2,[H|A]).
setb([H|T],[H2|T2],A) :- member(H,A),setb(T,[H2|T2],A).
setb([H|T],[],A) :- member(H,A),setb(T,[],A).
set(L,S) :- setb(L,S,[]).
You just have to stop the backtracking of Prolog.
enter code here
member(X,[X|_]):- !.
member(X,[_|T]) :- member(X,T).
set([],[]).
set([H|T],[H|Out]) :-
not(member(H,T)),
!,
set(T,Out).
set([H|T],Out) :-
member(H,T),
set(T,Out).
Using the support function mymember of Tim, you can do this if the order of elements in the set isn't important:
mymember(X,[X|_]).
mymember(X,[_|T]) :- mymember(X,T).
mkset([],[]).
mkset([T|C], S) :- mymember(T,C),!, mkset(C,S).
mkset([T|C], S) :- mkset(C,Z), S=[T|Z].
So, for example ?- mkset([1,4,1,1,3,4],S) give you as output:
S = [1, 3, 4]
but, if you want a set with the elements ordered like in the list you can use:
mkset2([],[], _).
mkset2([T|C], S, D) :- mkset2(C,Z,[T|D]), ((mymember(T,D), S=Z,!) ; S=[T|Z]).
mkset(L, S) :- mkset2(L,S,[]).
This solution, with the same input of the previous example, give to you:
S = [1, 4, 3]
This time the elements are in the same order as they appear in the input list.
/* Remove duplicates from a list without accumulator */
our_member(A,[A|Rest]).
our_member(A, [_|Rest]):-
our_member(A, Rest).
remove_dup([],[]):-!.
remove_dup([X|Rest],L):-
our_member(X,Rest),!,
remove_dup(Rest,L).
remove_dup([X|Rest],[X|L]):-
remove_dup(Rest,L).