Define the predicate Prolog - prolog

I'm reviewing some exercise for the coming test and having difficulty at this.
Given a list of integers L, define the predicate: add(L,S) which returns a list of integers S in which each element is the sum of all the elements in L up to the same position.
Example:
?- add([1,2,3,4,5],S).
S = [1,3,6,10,15].
So my question is what define the predicate means? It looks pretty general. I've read some threads but they did not provide much. Thanks!

This is a good exercise to familiarize yourself with two important Prolog concepts:
declarative integer arithmetic to reason about integers in all directions
meta-predicates to shorten your code.
We start with a very simple relation, relating an integer I and a sum of integers S0 to a new sum S:
sum_(I, S0, S) :- S #= S0 + I.
Depending on your Prolog system, you may need a directive like:
:- use_module(library(clpfd)).
to use declarative integer arithmetic.
Second, there is a powerful family of meta-predicates (see meta-predicate) called scanl/N, which are described in Richard O'Keefe's Prolog library proposal, and already implemented in some systems. In our case, we only need scanl/4.
Example query:
?- scanl(sum_, [1,2,3,4,5], 0, Sums).
Sums = [0, 1, 3, 6, 10, 15].
Done!
In fact, more than done, because we can use this in all directions, for example:
?- scanl(sum_, Is, 0, Sums).
Is = [],
Sums = [0] ;
Is = [_2540],
Sums = [0, _2540],
_2540 in inf..sup ;
Is = [_3008, _3014],
Sums = [0, _3008, _3044],
_3008+_3014#=_3044 ;
etc.
This is what we expect from a truly relational solution!
Note also the occurrence of 0 as the first element in the list of partial sums. It satisfies your textual description of the task, but not the example you posted. I leave aligning these as an exercise.

Define the predicate simply means write a predicate that does what the question requires.
In your question you have to write the definition of add/2 predicate( "/2" means that it has two arguments). You could write the definition below:
add(L,S):- add1(L,0,S).
add1([],_,[]).
add1([H|T],Sum,[H1|T1]):- H1 is Sum+H,NSum is Sum+H,add1(T,NSum,T1).
The above predicate gives you the desired output. A simple example:
?- add([1,2,3,4,5],S).
S = [1, 3, 6, 10, 15].
I think the above or something similar predicate is what someone would wait to see in a test.
Some additional information-issues
The problem with the predicate above is that if you query for example:
?- add(S,L).
S = L, L = [] ;
ERROR: is/2: Arguments are not sufficiently instantiated
As you see when you try to ask when your predicate succeeds it gives an obvious solutions and for further solutions it throws an error. This is not a very good-desired property. You could improve that by using module CLPFD:
:- use_module(library(clpfd)).
add(L,S):- add1(L,0,S).
add1([],_,[]).
add1([H|T],Sum,[H1|T1]):- H1 #= Sum+H,NSum #= Sum+H,add1(T,NSum,T1).
Now some querying:
?- add([1,2,3,4,5],S).
S = [1, 3, 6, 10, 15].
?- add(S,[1,3,6]).
S = [1, 2, 3].
?- add(S,L).
S = L, L = [] ;
S = L, L = [_G1007],
_G1007 in inf..sup ;
S = [_G1282, _G1285],
L = [_G1282, _G1297],
_G1282+_G1285#=_G1307,
_G1282+_G1285#=_G1297 ;
...and goes on..
As you can see now the predicate is in the position to give any information you ask! That's because now it has a more relational behavior instead of the functional behavior that it had before due to is/2 predicate. (These are some more information to improve the predicate's behavior. For the test you might not be allowed to use libraries etc... so you may write just a simple solution that at least answers the question).

Related

Function to find a list in prolog

I am new to Prolog and I am trying to write a function that finds a list that follows some rules.
More specifically, given two numbers, N and K, I want my function to find a list with K powers of two that their sum is N. The list must not contain each power but the total sum of each power. For example if N=13 and K=5, I want my list to be [2,2,1] where the first 2 means two 4, the second 2 means two 2, and the third 1 means one 1 (4+4+2+2+1=13). Consider that beginning from the end of the list each position i represents the 2^i power of 2. So I wrote this code:
sum2(List, SUM, N) :-
List = [] -> N=SUM;
List = [H|T],
length(T, L),
NewSUM is SUM + (H * 2**L),
sum2(T, NewSUM, N).
powers2(N,K,X):-
sum2(X,0,N),
sum_list(X, L),
K = L.
The problem is:
?- sum2([2,2,1],0,13).
true.
?- sum2([2,2,1],0,X).
X = 13.
?- sum2(X,0,13).
false.
?- powers2(X,5,[2,2,1]).
X = 13.
?- powers2(13,5,[2,2,1]).
true.
?- powers2(13,X,[2,2,1]).
X = 5.
?- powers2(13,5,X).
false.
In the cases, X represents the list I expected the output to be a list that follows the rules and not false. Could you help me to find how can I solve this and have a list for output in these cases?
The immediate reason for the failure of your predicate with an unbound list is due to your use of the -> construct for control flow.
Here is a simplified version of what you are trying to do, a small predicate for checking whether a list is empty or not:
empty_or_not(List, Answer) :-
( List = []
-> Answer = empty
; List = [H|T],
Answer = head_tail(H, T) ).
(Side note: The exact layout is a matter of taste, but you should always use parentheses to enclose code if you use the ; operator. I also urge you to never put ; at the end of a line but rather in a position where it really sticks out. Using ; is really an exceptional case in Prolog, and if it's formatted too similarly to ,, it can be hard to see that it's even there, and what parts of the clause it applies to.)
And this seems to work, right?
?- empty_or_not([], Answer).
Answer = empty.
?- empty_or_not([1, 2, 3], Answer).
Answer = head_tail(1, [2, 3]).
OK so far, but what if we call this with an unbound list?
?- empty_or_not(List, Answer).
List = [],
Answer = empty.
Suddenly only the empty list is accepted, although we know from above that non-empty lists are fine as well.
This is because -> cuts away any alternatives once it has found that its condition is satisfied. In the last example, List is a variable, so it is unifiable with []. The condition List = [] will succeed (binding List to []), and the alternative List = [H|T] will not be tried. It seems simple, but -> is really an advanced feature of Prolog. It should only be used by more experienced users who know that they really really will not need to explore alternatives.
The usual, and usually correct, way of implementing a disjunction in Prolog is to use separate clauses for the separate cases:
empty_or_not([], empty).
empty_or_not([H|T], head_tail(H, T)).
This now behaves logically:
?- empty_or_not([], Answer).
Answer = empty.
?- empty_or_not([1, 2, 3], Answer).
Answer = head_tail(1, [2, 3]).
?- empty_or_not(List, Answer).
List = [],
Answer = empty ;
List = [_2040|_2042],
Answer = head_tail(_2040, _2042).
And accordingly, your definition of sum2 should look more like this:
sum2([], SUM, N) :-
N = SUM.
sum2([H|T], SUM, N) :-
length(T, L),
NewSUM is SUM + (H * 2**L),
sum2(T, NewSUM, N).
This is just a small step, however:
?- sum2(X, 0, 13).
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR: [9] _2416 is 0+_2428* ...
ERROR: [8] sum2([_2462],0,13) at /home/gergo/sum.pl:5
ERROR: [7] <user>
You are trying to do arithmetic on H, which has no value. If you want to use "plain" Prolog arithmetic, you will need to enumerate appropriate values that H might have before you try to do arithmetic on it. Alternatively, you could use arithmetic constraints. See possible implementations of both at Arithmetics in Prolog, represent a number using powers of 2.

Prolog Program Not Merging Sorted Lists Correctly

I have a simple program I'm trying to write in Prolog. Essentially, as I learning exercise, I'm trying to write a program that takes two sorted lists as input, and returns the merged list that is also sorted. I have dubbed the predicate "merge2" as to no be confused with the included predicate "merge" that seems to do this already.
I am using recursion. My implementation is below
merge2([],[],[]).
merge2([X],[],[X]).
merge2([],[Y],[Y]).
merge2([X|List1],[Y|List2],[X|List]):- X =< Y,merge2(List1,[Y|List2],List).
merge2([X|List1],[Y|List2],[Y|List]):- merge2([X|List1],List2,List).
When I run this, I get X = [1,2,4,5,3,6] which is obviously incorrect. I've been able to code multiple times and tried to draw out the recursion. To the best of my knowledge, this should be returning the correct result. I'm not sure why the actualy result is so strange.
Thank you.
QuickCheck is your friend. In this case, the property that you want to verify can be expressed using the following predicate:
sorted(L1, L2) :-
sort(L1, S1),
sort(L2, S2),
merge2(S1, S2, L),
sort(L, S),
L == S.
Note that sort/2 is a standard Prolog built-in predicate. Using the QuickCheck implementation provided by Logtalk's lgtunit tool, which you can run using most Prolog systems, we get:
?- lgtunit::quick_check(sorted(+list(integer),+list(integer))).
* quick check test failure (at test 2 after 0 shrinks):
* sorted([0],[0])
false.
I.e. you code fails for L1 = [0] and L2 = [0]:
?- merge2([0], [0], L).
L = [0, 0] ;
L = [0, 0] ;
false.
Tracing this specific query should allow you to quickly find at least one of the bugs in your merge2/4 predicate definition. In most Prolog systems, you can simply type:
?- trace, merge2([0], [0], L).
If you want to keep duplicates in the merged list, you can use the de facto standard predicates msort/2 in the definition of the property:
sorted(L1, L2) :-
sort(L1, S1),
sort(L2, S2),
merge2(S1, S2, L),
msort(L, S),
L == S.
In this case, running QuickCheck again:
?- lgtunit::quick_check(sorted(+list(integer),+list(integer))).
* quick check test failure (at test 3 after 8 shrinks):
* sorted([],[475,768,402])
false.
This failure is more informative if you compare the query with your clauses that handle the case where the first list is empty...
This is done using difference list and since you are learning it uses reveals, AKA spoiler, which are the empty boxes that you have to mouse over to ravel the contents. Note that the reveals don't allow for nice formatting of code. At the end is the final version of the code with nice formatting but not hidden by a reveal so don't peek at the visible code at the very end if you want to try it for yourself.
This answer takes it that you have read my Difference List wiki.
Your basic idea was sound and the basis for this answer using difference list. So obviously the big change is to just change from closed list to open list.
As your code is recursive, the base case can be used to set up the pattern for the rest of the clauses in the predicate.
Your simplest base case is
merge2([],[],[]).
but a predicate using difference list can use various means to represent a difference list with the use of L-H being very common but not one I chose to use. Instead this answer will follow the pattern in the wiki of using two variables, the first for the open list and the second for the hole at the end of the open list.
Try to create the simple base case on your own.
merge2_prime([],[],Hole,Hole).
Next is needed the two base cases when one of the list is empty.
merge2_prime([X],[],Hole0,Hole) :-
Hole0 = [X|Hole].
merge2_prime([],[Y],Hole0,Hole) :-
Hole0 = [Y|Hole].
Then the cases that select an item from one or the other list.
merge2_prime([X|List1],[Y|List2],Hole0,Hole) :-
X =< Y,
Hole0 = [X|Hole1],
merge2_prime(List1,[Y|List2],Hole1,Hole).
merge2_prime(List1,[Y|List2],Hole0,Hole) :-
Hole0 = [Y|Hole1],
merge2_prime(List1,List2,Hole1,Hole).
Lastly a helper predicate is needed so that the query merge2(L1,L2,L3) can be used.
merge2(L1,L2,L3) :-
merge2_prime(L1,L2,Hole0,Hole),
Hole = [],
L3 = Hole0.
If you run the code as listed it will produce multiple answer because of backtracking. A few cuts will solve the problem.
merge2(L1,L2,L3) :-
merge2_prime(L1,L2,Hole0,Hole),
Hole = [],
L3 = Hole0.
merge2_prime([],[],Hole,Hole) :- !.
merge2_prime([X],[],Hole0,Hole) :-
!,
Hole0 = [X|Hole].
merge2_prime([],[Y],Hole0,Hole) :-
!,
Hole0 = [Y|Hole].
merge2_prime([X|List1],[Y|List2],Hole0,Hole) :-
X =< Y,
!,
Hole0 = [X|Hole1],
merge2_prime(List1,[Y|List2],Hole1,Hole).
merge2_prime(List1,[Y|List2],Hole0,Hole) :-
Hole0 = [Y|Hole1],
merge2_prime(List1,List2,Hole1,Hole).
Example run:
?- merge2([1,3,4],[2,5,6],L).
L = [1, 2, 3, 4, 5, 6].
?- merge2([0],[0],L).
L = [0, 0].
I didn't check this with lots of examples as this was just to demonstrate that an answer can be found using difference list.

Prolog list of list n number with condition

I'm studying prolog language and i have an issue regarding this problem.
I've already created a program that, given a number N, returns a list with elements between 0 and N:
list2val(N,L):- list2val(0,N,L).
list2val(N,N,[N]).
list2val(C,N,[C|T]):-
C<N,
N1 is C+1,
list2val(N1,N,T).
?- list2val(5,X).
X = [0,1,2,3,4,5]
Now i'm trying to give an extension that, given a list, returns a list of lists in which every list is list2val only if the next number is greater than current number. In this case:
?- newFuction([1,5,2,3,9],L).
L = [[0,1],[0,1,2,],[0,1,2,3]]
My code is this, but somethings is wrong:
array(X):- array(X,_L).
array([],_L).
array([H|[T|Ts]],L1):-
H<T,
list2val(H,L2),
array([T|Ts],[L1|[L2]]).
array([T|Ts],L1).
Maybe could be too much difficult to understand but using a list L = [1,5,2,3,9] i do those steps:
check 1<5 so i create a 1 list2val until 1..in this case [0,1]
check 5<2 i dont create nothing.
check 2<3 i create list2val of 2 ...[0,1,2]
and so on...
I don't want use a standard predicates, by implement with standard terms.
A solution for your problem could be:
list2val(N,L):- list2val(0,N,L).
list2val(N,N,[N]):- !.
list2val(C,N,[C|T]):-
C<N,
N1 is C+1,
list2val(N1,N,T).
simulate([_],[]).
simulate([A,B|T],[H|T1]):-
( A < B ->
list2val(A,H),
simulate([B|T],T1);
simulate([B|T],[H|T1])
).
Using a predicate like simulate/2, you can solve your problem: it compares two numbers of the list and then create a new list in case the condition is satisfied.
?- simulate([1,5,2,3,9],LO).
LO = [[0, 1], [0, 1, 2], [0, 1, 2, 3]]
false

Does prolog have a spread/splat/*args operator?

In many procedural languages (such as python), I can "unpack" a list and use it as arguments for a function. For example...
def print_sum(a, b, c):
sum = a + b + c
print("The sum is %d" % sum)
print_sum(*[5, 2, 1])
This code will print: "The sum is 8"
Here is the documentation for this language feature.
Does prolog have a similar feature?
Is there a way to replicate this argument-unpacking behaviour in Prolog?
For example, I'd like to unpack a list variable before passing it into call.
Could I write a predicate like this?
assert_true(Predicate, with_args([Input])) :-
call(Predicate, Input).
% Where `Input` is somehow unpacked before being passed into `call`.
...That I could then query with
?- assert_true(reverse, with_args([ [1, 2, 3], [3, 2, 1] ])).
% Should be true, currently fails.
?- assert_true(succ, with_args([ 2, 3 ]).
% Should be true, currently fails.
?- assert_true(succ, with_args([ 2, 4 ]).
% Should be false, currently fails.
Notes
You may think that this is an XY Problem. It could be, but don't get discouraged. It'd be ideal to receive an answer for just my question title.
You may tell me that I'm approaching the problem poorly. I know your intentions are good, but this kind of advice won't help to answer the question. Please refer to the above point.
Perhaps I'm approaching Prolog in too much of a procedural mindset. If this is the case, then what mindset would help me to solve the problem?
I'm using SWI-Prolog.
The built-in (=..)/2 (univ) serves this purpose. E.g.
?- G =.. [g, 1, 2, 3].
G = g(1,2,3).
?- g(1,2,3) =.. Xs.
Xs = [g,1,2,3].
However, note that many uses of (=..)/2 where the number of arguments is fixed can be replaced by call/2...call/8.
First: it is too easy, using unification and pattern matching, to get the elements of a list or the arguments of any term, if you know its shape. In other words:
sum_of_three(X, Y, Z, Sum) :- Sum is X+Y+Z.
?- List = [5, 2, 1],
List = [X, Y, Z], % or List = [X, Y, Z|_] if the list might be longer
sum_of_three(X, Y, Z, Sum).
For example, if you have command line arguments, and you are interested only in the first two command line arguments, it is easy to get them like this:
current_prolog_flag(argv, [First, Second|_])
Many standard predicates take lists as arguments. For example, any predicate that needs a number of options, as open/3 and open/4. Such a pair could be implemented as follows:
open(SrcDest, Mode, Stream) :-
open(SrcDest, Mode, Stream, []).
open(SrcDest, Mode, Stream, Options) :-
% get the relevant options and open the file
Here getting the relevant options can be done with a library like library(option), which can be used for example like this:
?- option(bar(X), [foo(1), bar(2), baz(3)]).
X = 2.
So this is how you can pass named arguments.
Another thing that was not mentioned in the answer by #false: in Prolog, you can do things like this:
Goal = reverse(X, Y), X = [a,b,c], Y = [c,b,a]
and at some later point:
call(Goal)
or even
Goal
To put it differently, I don't see the point in passing the arguments as a list, instead of just passing the goal as a term. At what point are the arguments a list, and why are they packed into a list?
To put it differently: given how call works, there is usually no need for unpacking a list [X, Y, Z] to a conjunction X, Y, Z that you can then use as an argument list. As in the comment to your question, these are all fine:
call(reverse, [a,b,c], [c,b,a])
and
call(reverse([a,b,c]), [c,b,a])
and
call(reverse([a,b,c], [c,b,a]))
The last one is the same as
Goal = reverse([a,b,c], [c,b,a]), Goal
This is why you can do something like this:
?- maplist(=(X), [Y, Z]).
X = Y, Y = Z.
instead of writing:
?- maplist(=, [X,X], [Y, Z]).
X = Y, Y = Z.

I don't understand what label does in Prolog

I went through the manual and documentation but still don't understand. I'm trying to implement a sudoku solution where after writing out all the other rules of the game, I've added label(Board) according to my teacher's instructions.
However I still don't get how it works or what it's doing. Shouldn't the other constraints(I have checks saying numbers have to be 1..9, row has to be all different,etc) give me the answer by themselves?
If you want to learn Prolog and CLP(FD) rapidly, use Prolog's top level shell to play around until you get comfortable with it. In fact, everything you need to know about CLP(FD) and Prolog can be explained there ; or almost. No need to write (what's their name?) files, everything fits in a line. Yes, I know, our parents warned us: My child, promise me, never do a one-liner. But you will learn so much faster.
So do you have the ?- waiting?
In traditional Prolog (without constraints) what you get back from a query is a so called answer substitution. In many situations, this answer substitution already describes a solution. This is the case if for each variable, a variable free term is found. Lets look at a concrete example and describe a list with 5 elements where each element is a value between 1 and 5. In this case, solutions are found for different values for L.
?- N = 5, length(L,N),maplist(between(1,N),L).
N = 5, L = [1,1,1,1,1]
; N = 5, L = [1,1,1,1,2]
; N = 5, L = [1,1,1,1,3]
; ... .
Prolog will show you only one solution (secretly hoping that you will be happy with it, it's a bit lazy, er non-strict). You get all of them typing SPACE or ;. Try it a bit just to see how many they are...
There is a total of 5^5 solutions. It's not very practical, if you just want to pick a few solutions out of that many. Large sets of solutions are represented quite ineffectively in that manner. And then, think of infinite sets! How can Prolog, or any finite being, enumerate an infinite set? We can only start to do so, finite as we are.
To overcome this, Prolog is not always forced to show concrete values, that is, solutions, but can subsume them a bit by showing answers instead:
?- N = 5, length(L,N).
N = 5, L = [_A,_B,_C,_D,_E].
This answer (-substitution) contains all 5^5 answers above, and many many more, like L = [stack,over,flow,dot,com]. In fact, it describes an infinite set of solutions! Didn't I say we finite beings can't do this? As long as we insist on concrete solutions we can't, but if we are happy with answers instead, we can do the impossible.
That idea can be extended to describe more specific sets. All with a single answer. For sets about integers, we have library(clpfd). Use it like so:
?- use_module(library(clpfd)).
?- asserta(clpfd:full_answer). % only necessary for SICStus
We can now restate our original query (in SWI, you can do Cursor up ↑ to get it):
?- N = 5, length(L,N),L ins 1..N.
N = 5, L = [_A,_B,_C,_D,_E],
_A in 1..5, _B in 1..5, _C in 1..5, _D in 1..5,_E in 1..5.
Now all 3125 solutions are compactly described with a single answer. (3125? that's 5^5). We can continue to state further requirements, like that they are all different:
?- N = 5, length(L,N),L ins 1..N, all_different(L).
N = 5, L = [_A,_B,_C,_D,_E],
_A in 1..5,_B in 1..5,_C in 1..5,_D in 1..5,_E in 1..5,
all_different([_A,_B,_C,_D,_E]).
What (practically) all constraints have in common is that they do not enumerate solutions, instead, they try to maintain consistency. Let's try this, by stating that the first element should be 1:
?- N = 5, length(L,N),L ins 1..N, all_different(L), L = [1|_].
N = 5, L = [1,_A,_B,_C,_D],
_A in 2..5,_B in 2..5,_C in 2..5,_D in 2..5,
all_different([1,_A,_B,_C,_D]).
Did you see the effect? They promptly changed their domains! Now they are all in 2..5.
And they should all be in 1..4:
?- N = 5, length(L,N),L ins 1..N, all_different(L), L = [1|_], L ins 1..4.
N = 5, L = [1,_A,_B,_C,_D],
_A in 2..4,_B in 2..4,_C in 2..4,_D in 2..4,
all_different([1,_A,_B,_C,_D]).
Again, they are updated. But ... think of it: There are 4 variables left, they should all be different but there are only 3 different values for them.
So we have caught Prolog being a bit too lazy. There actually is a better constraint called all_distinct/1 that would fail now, but no matter how many clever constraints a system has, there will be always such inconsistencies. Ask Professor Gödel. The only ways to bail out would be errors or infinite loops.
So we need another method to be sure that an answer does describe real solutions. Enter labeling! With label/1 or labeling/2 we can eliminate all those strange constraints and bust inconsistencies:
?- N = 5, length(L,N),L ins 1..N, all_different(L), L = [1|_], L ins 1..4, labeling([], L).
false.
?- N = 5, length(L,N),L ins 1..N, all_different(L), L = [1|_], labeling([], L).
N = 5, L = [1,2,3,4,5]
; N = 5, L = [1,2,3,5,4]
; N = 5, L = [1,2,4,3,5]
; ... .
How can we be sure that these are real solutions? Easy: They do not contain any extra goals besides answer substitutions1. For if we forgot some:
?- N = 5, length(L,N),L ins 1..N, all_different(L), L = [1,B,C|_], labeling([],[B,C]).
N = 5, L = [1,2,3,_A,_B], B = 2, C = 3,
_A in 4..5, _B in 4..5,
all_different([1,2,3,_A,_B]),
They would show.
SWI's labeling/2 has a very useful guarantee:
Labeling is always complete, always terminates, and yields no redundant solutions.
1 Since the SWI toplevel does not show all constraints, you would need to wrap call_residue_vars(Goal, Vs) around it. But for simple top level queries, above is good enough.
Roughly, there are 2 phases in constraint programming: constraint propagation and search.
Constraint propagation alone can give concrete values, and it often does. But in general, it only reduces domain (set of the possible values for a variable) to a smaller subset, and then you need search (label values from a subset, obtained with constraint propagation).
Very simple example (pseudocode):
A #:: 0..1,
B #:: 0..1,
A #\= B
Constraint propagation cannot solve this by itself, it cannot even reduce domain of A or B - it can only create a delayed constraint. After that a search (label) tries a value 0 for A, the delayed constraint fires up, and domain of B reduced to {1}.
In contrast, this can be solved with constraint propagation alone:
A #:: 1,
B #:: 0..1,
A #\= B

Resources