How to find max element in nested list in Prolog? - list

I am trying to find the maximum element in multilayered list (meaning list in list in list...) in Prolog. The thing is, I reviewed all the predicates 1 by 1 and they all work, except for the one that is actually supposed to solve my problem. My approach is to flatten the list (make it single-layered) and the find the maximum element in THAT list. This is my code:
is_list([]).
add([],L,L).
add([X|L1],L2,[X|L3]):-add(L1,L2,L3).
maximum([X|O],M) :- max(O,X,M),!.
max([X|O],Y,M) :- X=<Y, max(O,Y,M).
max([X|O],Y,M) :- X>Y, max(O,X,M).
max([],M,M).
flatten([],[]).
flatten([X|L1],[X|L2]):-not(is_list(X)),!,flatten(L1,L2).
flatten([X|L1],L2):-flatten(X,LX),flatten(L1,LL1),add(LX,LL1,L2).
maximum_in_multilayered_list(L,M):-flatten(L,L1),maximum(L1,N), M is N.
For some reason, I get the following error:
?- maximum_in_multilayered_list([1,[2,3],4],X).
ERROR: Type error: `[]' expected, found `[2,3]' (a list) ("x" must hold one character)
ERROR: In:
ERROR: [13] [2,3]=<1
ERROR: [12] max([[2|...],4],1,_7284) at c:/users/ace_m/documents/prolog/bp.pl:47
ERROR: [11] maximum([1,...|...],_7328) at c:/users/ace_m/documents/prolog/bp.pl:46
ERROR: [10] maximum_in_multilayered_list([1,...|...],_7366) at c:/users/ace_m/documents/prolog/bp.pl:75
ERROR: [9] <user>
Exception: (12) max([[2, 3], 4], 1, _7596) ? creep
I understand that the problem is that I am actually comparing a list of integers with an integer meaning they are incompatible types, but why does it even come to that? What am I doing wrong?

Remove your is_list([]) and it works.
As it is, any non-empty list is not considered to be is_list/1 material, so for [2,3] in [1,[2,3],4] the second clause in the flatten/2 definition applies, and adds X = [2,3] as is into the "flattened" list [X|L2].
But is_list/1 is already a built-in predicate which does exactly what you want.
Another way to implement this is with library(aggregate).
First we define a backtrackable predicate which enumerates all non-lists (i.e. "plain values") through the nested lists (taken from this somewhat related recent answer of mine):
nembr(Z, A) :- % member in nested lists
is_list(A), member(B,A), nembr(Z,B)
;
\+ is_list(A), A=Z.
Then
18 ?- nembr(X, [1,[2,3],4]).
X = 1 ;
X = 2 ;
X = 3 ;
X = 4 ;
false.
19 ?- use_module(library(aggregate)).
true
20 ?- L = [1,[2,3],4], aggregate( max(X), nembr(X,L), R).
L = [1, [2, 3], 4],
R = 4.

Related

Prolog: Reversed list -- can't find the error

I want to write a reverse/2 function. This is my code and I cannot figure out where the error is.
rev([]).
rev([H|T],X):-rev(T,X),append(T,H,_).
The output:
rev ([1,2,3,4], X).
false.
rev(?List1,?List2) is true when elements of List2 are in reversed order compared to List1
rev(Xs, Ys) :-
rev(Xs, [], Ys, Ys).
rev([], Ys, Ys, []).
rev([X|Xs], Rs, Ys, [_|Bound]) :-
rev(Xs, [X|Rs], Ys, Bound).
Output:
?- rev([1,2,3,4],X).
X = [4, 3, 2, 1].
?- rev([3,4,a,56,b,c],X).
X = [c, b, 56, a, 4, 3].
Explanation of rev/4
On call rev([X|Xs](1), Rs(2), Ys(3), [_|Bound](4))
[X|Xs](1) - List1, the input list in our case (we can either call rev(Z,[3,2,1]).)
Rs(2) - ResultList is a helping list, we start with an empty list and on every recursive call we push (adding as head member) a member from [X|Xs](1).
Ys(3) - List2, the output list (reversed list of List1)
[_|Bound](4) - HelpingList for bounding the length of Ys(3) (for iterating "length of Ys" times).
On every recursion call rev(Xs(5), [X|Rs](6), Ys(3), Bound(7)).,
we push head member X ([X|Xs](1)) to the front of Rs ([X|Rs](6)),
and iterating the next member of Ys (Bound(7),[_|Bound](4)).
The recursion ends when rev([](9), Ys(10), Ys(3), [](12)). is true.
Every [X|Xs](1) (now the list is empty [](9)) member moved in reversed order to Ys(10), we bounded the size of Ys(3) (using [_|Bound](4) and now it's empty [](12)).
Notice that append/3 - append(?List1, ?List2, ?List1AndList2).
was wrong used in your code, append(T,H,_) when H is not a List2 (it's the head member of the list).
Example use of append/2 and append/3:
?- append([[1,2],[3]],X). % append/2 - Concatenate a list of lists.
X = [1, 2, 3].
?- append([4],[5],X). % append/3 - X is the concatenation of List1 and List2
X = [4, 5].
You should not place a space between the functor name rev and the argument list. Usually this gives a syntax error:
Welcome to SWI-Prolog (threaded, 64 bits, version 7.7.1)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
?- rev ([1,2,3],X).
ERROR: Syntax error: Operator expected
ERROR: rev
ERROR: ** here **
ERROR: ([1,2,3],X) .
Otherwise I think the rev/4 solution aims at a bidirectional solution. If you don't need this, and want to go for an accumulator solution that doesn't leave a choice point, you can try:
reverse(X, Y) :-
reverse2(X, [], Y).
reverse2([], X, X).
reverse2([X|Y], Z, T) :-
reverse2(Y, [X|Z], T).

Prolog bigger from list element pairs to new list

I want to find the bigger value from a list's element's pairs.
Ie. list=[5,7,4,5,6,8] the pairs are [5,7], [7,4], [4,5] etc.
Right now I have this little code snippet:
bigger([],X).
bigger([E1],[H|E1]).
bigger([E1,E2|T],[H|_]):-
(E1>E2,bigger([E2|T],[H|E1]));
(E1<E2,bigger([E2|T],[H|E2])).
The solution should look like:
?- bigger([5,7,4,5,6,8],X).
X = [7,7,5,6,8,8]
EDIT:
Deleted the remove/3 lines, since they're wrong.
I'll give MY understanding of how the code works.
Empty given list check.
One element list check, adds it to output list end ([H|E1])
More than one element in given list, output list
3.1 First two element check (E1 >/< E2)
3.2 New recursive query without E1 (first element)
3.3 Whichever is bigger is output list's last element now.
First I'll show you my solution of your problem (and the result shouldn't be X = [7,7,5,6,8]? I'll make this version.)
gtr(X,Y,Y) :-
Y>=X.
gtr(X,_,X).
bigger([],[]).
bigger([_], []).
bigger([X,Y|R], [Z|H]) :-
bigger([Y|R],H), gtr(X,Y,Z),!.
If you want to have last element appear in this list anyway than just change second bigger function.
Since the relation is describing lists you could opt to use DCGs for the task:
max_of(X,X,Y) :- X >= Y. % X is maximum if X>=Y
max_of(Y,X,Y) :- Y > X. % Y is maximum if Y>X
list_biggers(L,B) :-
phrase(biggers(L),B). % the DCG biggers//1 describes B based on L
biggers([]) --> % if the list is empty
[]. % there's no element in the biggers list
biggers([X]) --> % if the list contains just one element
[X]. % it is in the biggers list
biggers([X,Y|Xs]) --> % if the list contains at least two elements
{max_of(M,X,Y)}, % the maximum of them
[M], % is in the biggers list
biggers([Y|Xs]). % the same holds for [Y|Xs]
This definition is sticking to your reading of the task, that is, in the case of a one-element list the only element is in the list of bigger elements:
?- list_biggers([5,7,4,5,6,8],B).
B = [7, 7, 5, 6, 8, 8] ;
false.
?- list_biggers([1],B).
B = [1] ;
false.
If you prefer the reading suggested by #Armatorix, just change the second DCG-rule to
biggers([_X]) -->
[].
This way the queries above yields the following results:
?- list_biggers([5,7,4,5,6,8],B).
B = [7, 7, 5, 6, 8] ;
false.
?- list_biggers([1],B).
B = [] ;
false.
Note that the list has to be sufficiently instantiated. Otherwise you get an error:
?- list_biggers([X,Y,Z],B).
ERROR: >=/2: Arguments are not sufficiently instantiated
If the list only contains integers, you can remedy this problem by using CLP(FD). Add a line to include the library and change max_of/2 like so:
:- use_module(library(clpfd)).
max_of(X,X,Y) :- X #>= Y.
max_of(Y,X,Y) :- Y #> X.
Now the query above delivers all 4 expected solutions:
?- list_biggers([X,Y,Z],B).
B = [X, Y, Z],
X#>=Y,
Y#>=Z ;
B = [X, Z, Z],
X#>=Y,
Y#=<Z+ -1 ;
B = [Y, Y, Z],
X#=<Y+ -1,
Y#>=Z ;
B = [Y, Z, Z],
X#=<Y+ -1,
Y#=<Z+ -1 ;
false.
In order to construct logical programs, one needs to think logical. Based on the problem statement, there are three possibilities here:
we have an empty list, in that case the result is an empty list as well:
bigger([],[]).
in case we have a list with one element, the problem is underspecified. I would say that the result should be an empty list, but your example seems to suggest that we return that number, since we then have a 1-tuple, and the maximum of a 1-tuple is of course the single element in the tuple:
bigger([H],[H]).
in case the list contains two or more elements [H1,H2|T], then H1 and H2 are the first two elements. In that case we construct a vitual tuple in our head [H1,H2] and calculate the maximum, which is thus M is max(H1,H2). We prepend M to the resulting list of the recursion. That recursion is done on the list [H2|T]: the list where we popped H1 from:
bigger([H1,H2|T],[M|U]) :-
M is max(H1,H2),
bigger([H2|T],U).
Or putting this all together:
bigger([],[]).
bigger([H],[H]).
bigger([H1,H2|T],[M|U]) :-
M is max(H1,H2),
bigger(T,U).

Can someone please help explain this copy function works?

copyList([], []). % base case
copyList([H|T], [H|R]) :-
copyList(T, R).
I "sort of" understand how recursion works, but when I analysed this function, I got really confused. Can someone please explain, step-by-step what happens in this function and how it reaches the end using the example below:
?- copyList([1,2,3],L).
To understand what happens, you must see Prolog as a theorem solver: when you give Prolog the query ?- copyList([1, 2, 3], L)., you're essentially asking Prolog to prove that copyList([1, 2, 3], L) is true.
Prolog will therefore try to prove it. At its disposal, it has two clauses:
copyList([], []).
copyList([H|T], [H|R]):-
copyList(T, R).
As it is the first that it encounters, Prolog wil try to prove that copyList([1, 2, 3], L) is true by using the clause copyList([], []).
To do so, and since the clause has no body (nothing after :-), it would just have to unify the arguments of your query with the arguments of the clause (unify [1, 2, 3] with [] and L with []). While it is easy to unify L5 with [] (with the unification L5 = []), it is impossible to unify [1, 2, 3] with []. Therefore Prolog has failed to prove your query by using the first clause at its disposal. It must then try to use the second.
Once again it will unify the query arguments with the clause arguments to see if the clause is applicable: here it can do so, with the unifications H = 1, T = [2, 3], L = [H|R]. Now it has to see if the conditions listed after :- are respected, so it has to prove copyList(T, R). The exact same thing goes on twice, until it finds itself trying to prove copyList([], R). There, the first clause is applicable, and its job is over.
You can sum up the execution with a drawing as follows:
copyList([1, 2, 3], L).
|
| try to use clause number 1, doesn't unify with arguments.
| use clause number 2 and L = [1|R]
|
` copyList([2, 3], R).
|
| try to use clause number 1, doesn't unify with arguments.
| use clause number 2 and R = [2|R2]
|
` copyList([3], R2).
|
| try to use clause number 1, doesn't unify with arguments.
| use clause number 2 and R2 = [3|R3]
|
` copyList([], R3).
|
| use clause number 1 and R3 = []. One solution found
| try to use clause number 2, doesn't unify with arguments.
| No more possibilities to explore, execution over.
Now that the execution is over, we can see what the original L is by following the chain of unifications:
L = [1|R]
R = [2|R2]
R2 = [3|R3]
R3 = []
R2 = [3]
R = [2, 3]
L = [1, 2, 3]
Thanks to Will Ness for his original idea on how to explain the final value of a variable.
While your specific question was already answered, few remarks.
First, you could just as well call ?- copyList(L,[1,2,3]). or ?- copyList([1,2,3],[1,2|Z]). etc. What's important is that both lists can be of equal length, and their elements at the corresponding positions can be equal (be unified), because the meaning of the predicate is that its two argument lists are the same - i.e. of the same length, and having the same elements.
For example, the first condition can be violated with the call
?- copyList(X, [A|X]).
because it says that the 2nd argument is one element longer than the first. Of course such solution can not be, but the query will never terminate, because the first clause won't ever match and the second always will.

Prolog: How "length(+,-)" delete unassigned tail of the list keeping the list?

Again a Prolog beginner :-}
I build up a list element by element using
(1)
member(NewElement,ListToBeFilled).
in a repeating call,
(2)
ListToBeFilled = [NewElement|TmpListToBeFilled].
in a recursive call like
something(...,TmpListToBeFilled).
A concrete example of (2)
catch_all_nth1(List, AllNth, Counter, Result) :-
[H|T] = List,
NewCounter is Counter + 1,
(
0 is Counter mod AllNth
->
Result = [H|Result1]
;
Result = Result1
),
catch_all_nth1(T,AllNth,NewCounter,Result1),
!.
catch_all_nth1([], _, _, _).
As result I get a list which looks like
[E1, E2, E3, ..., Elast | _G12321].
Of course, the Tail is a Variable. [btw: are there better method to fill up the
list, directly avoiding the "unassigned tail"?]
I was now looking for a simple method to eliminate the "unassigned tail".
I found:
Delete an unassigned member in list
there it is proposed to use:
exclude(var, ListWithVar, ListWithoutVar),!,
[Found this too, but did not help as I do not want a dummy element at the end
Prolog list has uninstantiated tail, need to get rid of it ]
What I noticed is that using length\2 eliminate the "unassigned tail", too, and in addtion
the same List remains.
My Question is: How does it work? I would like to use the mechanism to eliminate the unassigned tail without using a new variable... [in SWI Prolog 'till now I did not get the debugger
entering length() ?!]
The example:
Z=['a','b','c' | Y],
X = Z,
write(' X '),write(X),nl,
length(X,Tmp),
write(' X '),write(X),nl.
13 ?- test(X).
X [a,b,c|_G3453]
X [a,b,c]
X = [a, b, c] .
I thought X, once initialized can not be changed anymore and you need
a new variable like in exclude(var, ListWithVar, ListWithoutVar).
Would be happy if someone explain the trick to me...
Thanks :-)
You're right about the strange behaviour: it's due to the ability of length/2 when called with unbound arguments
The predicate is non-deterministic, producing lists of increasing length if List is a partial list and Int is unbound.
example:
?- length([a,b,c|X],N).
X = [],
N = 3 ;
X = [_G16],
N = 4 ;
X = [_G16, _G19],
N = 5 ;
...
For your 'applicative' code, this tiny correction should be sufficient. Change the base recursion clause to
catch_all_nth1([], _, _, []).
here are the results before
4 ?- catch_all_nth1([a,b,c,d],2,1,R).
R = [b, d|_G75].
and after the correction:
5 ?- catch_all_nth1([a,b,c,d],2,1,R).
R = [b, d].
But I would suggest instead to use some of better know methods that Prolog provide us: like findall/3:
?- findall(E, (nth1(I,[a,b,c,d],E), I mod 2 =:= 0), L).
L = [b, d].
I think this should do it:
% case 1: end of list reached, replace final var with empty list
close_open_list(Uninstantiated_Var) :-
var(Uninstantiated_Var), !,
Uninstantiated_Var = '[]'.
% case 2: not the end, recurse
close_open_list([_|Tail]) :-
close_open_list(Tail).
?- X=[1,2,3|_], close_open_list(X).
X = [1, 2, 3].
Note that only variable X is used.. it simply recurses through the list until it hits the var at the end, replaces it with an empty list, which closes it. X is then available as a regular 'closed' list.
Edit: once a list element has been assigned to something specific, it cannot be changed. But the list itself can be appended to, when constructed as an open list ie. with |_ at the end. Open lists are a great way to build up list elements without needing new variables. eg.
X=[1,2,3|_], memberchk(4, X), memberchk(5,X).
X = [1, 2, 3, 4, 5|_G378304]
In the example above, memberchk tries tries to make '4', then '5' members of the list, which it succeeds in doing by inserting them into the free variable at the end in each case.
Then when you're done, just close it.

How do I turn the outputs of a function into a list?

I have a function that outputs names that fit a specific constraint. This function is fine.
But I need to use that function to make another function that turns the outputs of the former function into a list. Being a complete beginner with Prolog, I have no clue how to do this.
My problem is that I don't know how to iterate over the outputs to append it to an accumulator. The function which outputs names does so, then I press ";" or SPACE and it outputs the next answer until it's out of answers. I figure this means I have to make multiple calls to the function then append it. But I don't know how many times I need to call it, since I can't iterate over it like a list with [Head|Tail].
Here's what I have so far(although it's probably wrong):
%p1(L,X) determines if chemicals in List X are in any of the products and stores those products in L
p1(L,X) :- p1_helper(L,X,[]).
p1_helper(L,X,Acc) :- has_chemicals(A,X),append(Acc,[A],K),L=K, p1_helper(L,X,K).
function that outputs names with query has_chemicals(X,[List of Chemicals]).:
%has_chemicals(X,Is) determines if the chemicals in List Is are in the chemical list of X.
has_chemicals(X,Is) :- chemicals(X,Y), hc(Y,Is).
%hc(X,Y) determines if elements of Y are in elements of X.
hc(Y,[]).
hc(Y,[C|D]) :- isin(C,Y), hc(Y,D).
Any help is appreciated.
But I need to use that function to make another function that turns the outputs of the former function into a list. Being a complete beginner with Prolog, I have no clue how to do this.
findall(+Template, :Goal, -Bag):
Creates a list of the instantiations Template gets successively on backtracking over Goal and unifies the result with Bag.
For example, how to collect all odd numbers from 1 to 15:
odd( X ) :-
X rem 2 =:= 1.
We can get all that odds one-by-one.
?- between( 1, 15, X ), odd( X ).
X = 1 ;
X = 3 ;
X = 5 ;
X = 7 ;
X = 9 ;
X = 11 ;
X = 13 ;
X = 15.
And we can collect them into a list:
?- findall(X, (between( 1, 15, X ), odd( X )), List).
List = [1, 3, 5, 7, 9, 11, 13, 15].
I think you are looking for a way to capture the output of isin/2. Then you can use the builtin with_output_to/2, and combine it with findall/3, as suggested by other answers.
I encourage you to visit this page especially if you use swi-prolog.
There are 4 predicates that do what you want : findall/3, findall/4, bagof/3 and setof/3.
To summarize, here is the test predicate I'll be working with :
test(0, 3).
test(1, 3).
test(2, 5).
test(3, 4).
First, the simplest, findall/3 and findall/4 :
?- findall(C, test(X, C), Cs).
Cs = [3, 3, 5, 4].
?- findall(C, test(X, C), Cs, TailCs).
Cs = [3, 3, 5, 4|TailCs].
They just return all the alternatives, with duplicates, without sorting, without binding the other free variables, as a normal list for findall/3 and difference list for findall/4. both findalls predicates succeed when the list is empty.
Then, bagof. Basically, bagof/3 works as findall/3 but binds free variables. That means that the same query than above but with bagof/3 returns :
?- bagof(C, test(X, C), Cs).
X = 0,
Cs = [3] ;
X = 1,
Cs = [3] ;
X = 2,
Cs = [5] ;
X = 3,
Cs = [4].
By telling bagof/3 not to bind all the free variables, you obtain findall/3 :
?- bagof(C, X^test(X, C), Cs).
Cs = [3, 3, 5, 4].
Still you have to note that bagof/3 fails when the result is empty, where findall/3 doesn't.
Finally, setof/3. It's basically bagof/3 but with the results sorted and no duplicates :
?- setof(C, X^test(X, C), Cs).
Cs = [3, 4, 5].