Reputation: 375
I am trying to learn more about lists in Prolog, especially lists within a list. So I want to write a predicate to determine if the lists in a list are equal. So if I did this
?- equalLists([[a,b,c],[1,2,3],[d,4,e],[5,6]]).
false
So I'm trying to check each list to see if it is has the same length as the previous list. Can someone point me in the right direction?
Upvotes: 3
Views: 4108
Reputation: 18726
The next dish on my menu: the baroque clpfd prolog-coroutining hodgepodge.
:- use_module(library(clpfd)).
samelength_of(N,Xss) :- maplist(length_of__lazy(N),Xss).
length_of__lazy(N,Xs) :-
N #>= 0,
( nonvar(N)
-> length(Xs,N)
; var(Xs)
-> when((nonvar(Xs);nonvar(N)), length_of__lazy(N,Xs))
; Xs = []
-> N = 0
; Xs = [_|Xs0]
-> N0 + 1 #= N,
length_of__lazy(N0,Xs0)
; throw(error(type_error(list,Xs),length_of__lazy/2))
).
my_indomain(N) :-
fd_inf(N,I),
( N #= I
; N #> I, my_indomain(N)
).
Some sample queries:
?- Xss = [As,Bs,Cs], As=[], samelength_of(N,Xss). N = 0, Xss = [[],[],[]], As = [], Bs = [], Cs = []. ?- Xss = [As,Bs,Cs], samelength_of(N,Xss), As=[]. N = 0, Xss = [[],[],[]], As = [], Bs = [], Cs = [].
Some more? Want to try the flounder?
?- samelength_of(N,[As,Bs,Cs]).
N in 0..sup,
when((nonvar(As);nonvar(N)), length_of__lazy(N,As)),
when((nonvar(Bs);nonvar(N)), length_of__lazy(N,Bs)),
when((nonvar(Cs);nonvar(N)), length_of__lazy(N,Cs)).
Flounder is not your taste? No problemo!
?- samelength_of(N,[As,Bs,Cs]), my_indomain(N).
N = 0, As = [], Bs = [], Cs = [] ;
N = 1, As = [_A1], Bs = [_B1], Cs = [_C1] ;
N = 2, As = [_A1,_A2], Bs = [_B1,_B2], Cs = [_C1,_C2] ;
N = 3, As = [_A1,_A2,_A3], Bs = [_B1,_B2,_B3], Cs = [_C1,_C2,_C3] ...
Upvotes: 2
Reputation: 18663
Follows a second solution with better termination properties compared with my first attempt. The main idea is at each traversal of the list of lists, we drop a single element from every list.
equal_lengths([]).
equal_lengths([L1| Ls]) :-
pick(L1, Ls, Rs),
equal_lengths(Rs).
pick([], Ls, []) :-
all_empty(Ls).
pick([_| R1], Ls, [R1| Rs]) :-
pick(Ls, Rs).
pick([], []).
pick([[_|R1]| Ls], Rs) :-
pick([_|R1], Ls, Rs).
all_empty([]).
all_empty([[]| Rs]) :-
all_empty(Rs).
The problematic case @false mentioned in a comment to my first solution was:
| ?- equal_lengths([_,_,[]]).
true ? ;
no
It's more clear, however, that we get the single correct solution if we don't use anonymous variables:
| ?- equal_lengths([L1,L2,[]]).
L1 = []
L2 = [] ? ;
no
All the previous sample queries in my first solution pose no problems. One query in particular is worth mention, as it wrongly only provided a single solution instead of generating solutions in the previous attempt. Now it works as expected:
| ?- equal_lengths([L]).
L = [] ? ;
L = [_] ? ;
L = [_,_] ? ;
L = [_,_,_] ? ;
...
Can anyone find a sample query leading to trouble with this solution?
Upvotes: 2
Reputation: 18663
A solution that takes advantage of the first-argument indexing found in most Prolog systems to avoid spurious choice-points in most (but not all) cases:
equal_lengths([]).
equal_lengths([L1| Ls]) :-
equal_lengths_aux(Ls, L1).
equal_lengths_aux([], _).
equal_lengths_aux([L2| Ls], L1) :-
equal_length(L1, L2),
equal_lengths_aux(Ls, L2).
equal_length([], []).
equal_length([_| Tail1], [_| Tail2]) :-
equal_length(Tail1, Tail2).
Some sample queries:
| ?- equal_lengths([]).
yes
| ?- equal_lengths([[]]).
yes
| ?- equal_lengths([_]).
yes
| ?- equal_lengths([[],_]).
yes
| ?- equal_lengths([_,[]]).
true ? ;
no
| ?- equal_lengths([L1,L2]).
L1 = []
L2 = [] ? ;
L1 = [_]
L2 = [_] ? ;
L1 = [_,_]
L2 = [_,_] ?
...
| ?- equal_lengths([[a,b,c],[1,2,3],[d,4,e],[5,6]]).
no
| ?- equal_lengths([[a,b,c],[1,2,3],[d,4,e],[5,6,7],L]).
L = [_,_,_]
yes
| ?- equal_lengths([L1,[_,_],L3]).
L1 = [_,_]
L3 = [_,_] ? ;
no
| ?- equal_lengths([L1,[_,_|_],L3]).
L1 = [_,_]
L3 = [_,_] ? ;
L1 = [_,_,_]
L3 = [_,_,_] ? ;
L1 = [_,_,_,_]
L3 = [_,_,_,_] ? ;
...
We only get a spurious choice-point (i.e. a choice-point that doesn't lead to a solution) when the first element is unbound and there are bound list elements. If no list element is bound to a finite list, the predicate generates solutions where the list length keeps growing as illustrated in the sample queries.
Upvotes: 2
Reputation: 18726
With the right tools---the meta-predicate maplist/2
and Prolog lambdas---all we need is one line:
?- Xss = [[1,2],[2,3],[3,4,5]], maplist(N+\Xs^length(Xs,N),Xss). false. ?- Xss = [[1,2],[2,3],[3,4]], maplist(N+\Xs^length(Xs,N),Xss). N = 2.
(+\)/2
helps us state that N
is free, so we use the same N
as the length of each Xs
in Xss
.
Upvotes: 1
Reputation: 60004
I'll rewrite the Peteris answer (+1) using SWI-Prolog builtins maplist and aggregate:
equallists(L) :-
maplist(length, L, Lengths),
aggregate(max(T), member(T, Lengths), N),
aggregate(min(T), member(T, Lengths), N).
Done!
Even simpler, using lambda (here the doc page) to adjust arguments order:
:- [lambda].
equallists([H|T]) :-
length(H, N),
maplist(\L^length(L, N), T).
Variazione sul tema (this should be minimal):
equallists([H|T]) :-
length(H, N),
forall(member(L, T), length(L, N)).
As @false noted, when T is not ground, the test can fail. A possible correction:
equallists([H|T]) :-
length(H, N),
forall(member(L, T), (nonvar(L), length(L, N))).
forall/2, that I think could be described as a form of failure driven loop, can be easily misusedit.
OTOH, every control flow construct in Prolog can be difficult to use properly, and this is perhaps the main cause of the scarce popularity of the language.
Upvotes: 2
Reputation: 22803
@Peteris's solution is unnecessarily complex. You can do it like this:
equal_lengths([]).
equal_lengths([[]]).
equal_lengths([[_|_]]).
equal_lengths([X,Y|Rest]) :-
length(X, Len),
length(Y, Len),
equal_lengths([Y|Rest]).
Think inductively. I'm asserting that the length of the empty list and a list of one list are "equal" (there are no/just one other to compare to). Then I say if the length of the first item equals the length of the second item, as long as the lengths of the second item and the rest match we are good.
Note: we're not explicitly saying that the length of X and Y is the same with some kind of equality test. We're letting Prolog handle that for us, by simply declaring that the length of X and Y is Len. So if the length of Y doesn't unify with the length of X, the predicate will fail.
Reversing the process
So, to write a predicate to determine if none of the lists have the same length we must observe that this time we will have to keep track of which lengths have been seen so far to check against. We must compare each list's length to all the preceeding list lengths to determine inequality. So this time our initial case will create the initial list of lengths and defer processing to another predicate like so:
unequal_lengths(X) :- unequal_lengths(X, []).
Now we again begin with similar base cases:
unequal_lengths([], _).
unequal_lengths([[]], _).
unequal_lengths([[_|_]], _).
Things get interesting when we have an actual list:
unequal_lengths([X|Rest], Lengths) :-
length(X, Len),
\+ member(Len, Lengths),
unequal_lengths(Rest, [Len|Lengths]).
So we're calculating the length of this list, then asserting that this is not a length we have seen before with the handy member predicate, then passing this length along with the rest along to the remainder of the list.
Addendum: unequal w/ forall
Inspired by the other answers, you can implement unequal_lengths in a higher-order fashion like so:
unequal_lengths(Lists) :-
findall(Len, (member(X, Lists), length(X, Len)), Lengths),
forall(select(Len, Lengths, Remaining), \+ member(Len, Remaining)).
If you think about it, this corresponds quite closely to a formal logic expression of the problem: for every list length, there does not exist an element of the remaining list lengths corresponding to this one.
Upvotes: 3
Reputation: 7493
I find the only acceptable solution to be chac's last one, for sake of completness I'd add the empty list handling though :
equalLengths([]).
equalLengths([Head|Tail]) :-
length(Head, Length),
forall(member(List, Tail), length(List, Length)).
Upvotes: -2
Reputation: 3756
First, we define some standard higher order relations, map
and fold
. This requires the built-in call
predicate. One could just define maxlist
etc. as one-offs, but this should be more illuminating.
The idea is to get a list of lengths and then compare if the maximum number in the list is equal to the minimum.
maplist(_, [], []).
maplist(P, [X | Y], [A | B]) :-
call(P, X, A),
maplist(P, Y, B).
max(A, B, M) :- A < B, M = B.
max(A, B, M) :- A >= B, M = A.
min(A, B, M) :- B < A, M = B.
min(A, B, M) :- B >= A, M = A.
fold(_, [X], X).
fold(P, [X, Y], R) :- call(P, X, Y, R).
fold(P, [X, Y | Z], R) :-
fold(P, [Y | Z], NR),
call(P, NR, X, R).
maxlist(L, M) :- fold(max, L, M).
minlist(L, M) :- fold(min, L, M).
equallists(L) :-
maplist(length, L, Lengths),
maxlist(Lengths, Max),
minlist(Lengths, Min),
Max == Min.
Upvotes: 4