Collect all elements of binary tree that are power of 2 - prolog

I can't get the following to work. This is what I got so far:
stepen(2).
stepen(X):-
X mod 2=:=0,
X1 is X/2,
stepen(X1).//stepen means power(in Serbian).
spoji([],Y,Y).
spoji([X|Xs],Y,[X|Z]):-spoji(Xs,Y,Z).//spoji means append lists
vadi(nil,[]).
vadi(t(X,L,R),[X|Xs]) :-
stepen(X),
vadi(L,SL),
vadi(R,SR),
spoji(SL,SR,Xs).//list of nodes that are power of 2.

You might find this method of determine whether or not N is a a power of 2 a little more efficient. It's a bit-twiddling hack that takes advantage of the two's complement representation of integer values:
is_power_of_two( N ) :-
integer(N) ,
N \= 0 ,
0 is N /\ (N-1)
.
Edited to note that the property holds true regardless of the sign of the integer: with one exception — 0, hence the test for non-zero — the only two's-complement integer values for which this property is true are powers of two:
?- between(-1025,+1025,N),pow2(N).
N = 1 ;
N = 2 ;
N = 4 ;
N = 8 ;
N = 16 ;
N = 32 ;
N = 64 ;
N = 128 ;
N = 256 ;
N = 512 ;
N = 1024 ;
false.

(So far nobody commented your code. So I will try)
stepen/1 loops
I assume you refer here to the non-negative powers of two. That is, 2^(-1) and the like are not considered.
First of all, your stepen/1 definition produces an error in ISO conforming systems like gnu-prolog or sicstus-prolog.
| ?- stepen(6).
! Type error in argument 2 of (is)/2
! expected an integer, but found 3.0
! goal: _193 is 3.0 mod 2
This is due to X1 is X/2 which always produces a float or an error, but never an integer. You may replace this by X1 is X div 2 or equivalently X1 is X >> 1.
Will this program now always terminate? After all X div 2 will approach zero. From the negative side, it will end at -1 which then will fail. But from the positive side, it will stay at 0!
Here is the looping program (failure-slice) reduced to its minimum:
?- stepen(0).
stepen(2) :- false.
stepen(X):-
X mod 2=:=0,
X1 is X div 2,
stepen(X1), false. % stepen means power(in Serbian).
As Nicholas Carey has suggested, you can simplify this predicate to:
stepen(X) :-
X > 0,
X /\ (X-1) =:= 0.
vadi/2 logic
In your definition, this predicate is true, if all nodes of the trees are powers of two. I assume you wanted to "filter out" the powers. The easiest way to do this is by using DCGs instead of spojii/3 vl. append/3. Let's first consider a simpler case, just the nodes of a tree:
nodes(nil) --> [].
nodes(t(X, L, R)) -->
[X],
nodes(L),
nodes(R).
?- T = t(1,nil,t(2,t(3,nil,t(4,nil,nil)),t(5,nil,nil))), phrase(nodes(T),L).
T = t(1,nil,t(2,t(3,nil,t(4,nil,nil)),t(5,nil,nil))), L = [1,2,3,4,5].
Now, you no longer want all elements, but only certain, I will use a separate nonterminal for that:
st(E) --> {stepen(E)}, [E].
st(E) --> {\+stepen(E)}. % nothing!
Or more compactly:
st(E) --> {stepen(E)} -> [E] ; [].
Now, the final non-terminal is:
stepeni(nil) --> [].
stepeni(t(X,L,R)) -->
st(X),
stepeni(L),
stepeni(R).
?- T = t(1,nil,t(2,t(3,nil,t(4,nil,nil)),t(5,nil,nil))), phrase(stepeni(T),L).
T = t(1,nil,t(2,t(3,nil,t(4,nil,nil)),t(5,nil,nil))), L = [1,2,4].

If you consider that 1 is 2^0, you need to change the base case of stepen/1 predicate.
A more important correction is required because your vadi/2 predicate will fail when any node not power of 2 is found in the tree.
Then you should add a clause
vadi(t(X,L,R),Xs) :-
% \+ stepen(X), this test is not mandatory, but it depends on *where* you add the clause
vadi(L,SL), vadi(R,SR), spoji(SL,SR,Xs).

Related

Recursion confuses me

I have understood the theory part of Recursion. I have seen exercises but I get confused. I've tried to solve some, some I understand and some I don't. This exercise is confusing me. I can't understand why, so I use comments to show you my weak points. I should have power (X,N,P) so P=X^N.
Some examples:
?- power(3,5,X).
X = 243
?- power(4,3,X).
X = 64
?- power(2,4,X).
X = 16
The solution of this exercise is: (See comments too)
power(X,0,1). % I know how works recursion,but those numbers 0 or 1 why?
power(X,1,X). % X,1,X i can't get it.
power(X,N,P) :- % X,N,P if only
N1 is N-1, % N1=N-1 ..ok i understand
power(X,N1,P1), % P1 is used to reach the the P
P is P1*X. % P = P1*X
What I know recursion, I use a different my example
related(X, Y) :-
parent(X, Z),
related(Z, Y).
Compare my example with the exercise. I could say that my first line, what I think. Please help me out with it is a lot of confusing.
related(X, Y) :- is similar to power(X,N,P) :- . Second sentence of my example parent(X, Z), is similar to N1 is N-1, and the third sentence is related(Z, Y). similar to power(X,N1,P1), and P is P1*X..
Let's go over the definition of the predicate step by step. First you have the fact...
power(X,0,1).
... that states: The 0th power of any X is 1. Then there is the fact...
power(X,1,X).
... that states: The 1st power of any X is X itself. Finally, you have a recursive rule that reads:
power(X,N,P) :- % P is the Nth power of X if
N1 is N-1, % N1 = N-1 and
power(X,N1,P1), % P1 is the N1th power of X and
P is P1*X. % P = P1*X
Possibly your confusion is due to the two base cases that are expressed by the two facts (one of those is actually superfluous). Let's consider the following queries:
?- power(5,0,X).
X = 1 ;
ERROR: Out of local stack
The answer 1 is certainly what we expect, but then the predicate loops until it runs out of stack. That's certainly not desirable. And this query...
?- power(5,1,X).
X = 5 ;
X = 5 ;
ERROR: Out of local stack
... yields the correct answer twice before running out of stack. The reason for the redundant answer is that the recursive rule can reduce any given N to zero and to one thus yielding the same answer twice. If you look at the structure of your recursive rule, it is obvious that the first base case is sufficient, so let's remove the second. The reason for looping out of stack is that, after N becomes zero, the recursive rule will search for other solutions (for N=-1, N=-2, N=-3,...) that do not exist. To avoid that, you can add a goal that prevents the recursive rule from further search, if N is equal to or smaller than zero. That leaves you with following definition:
power(X,0,1). % the 0th power of any X is 1
power(X,N,P) :- % P is the Nth power of X if
N > 0, % N > 0 and
N1 is N-1, % N1 = N-1 and
power(X,N1,P1), % P1 is the N1th power of X and
P is P1*X. % P = P1*X
Now the predicate works as expected:
?- power(5,0,X).
X = 1 ;
false.
?- power(5,1,X).
X = 5 ;
false.
?- power(5,3,X).
X = 125 ;
false.
I hope this alleviates some of your confusions.

Defining a mathematical language in prolog

So I have this mathematical language, it goes like this:
E -> number
[+,E,E,E] //e.g. [+,1,2,3] is 1+2+3 %we can put 2 to infinite Es here.
[-,E,E,E] //e.g. [-,1,2,3] is 1-2-3 %we can put 2 to infinite Es here.
[*,E,E,E] //e.g. [*,1,2,3] is 1*2*3 %we can put 2 to infinite Es here.
[^,E,E] //e.g. [^,2,3] is 2^3
[sin,E] //e.g. [sin,0] is sin 0
[cos,E] //e.g. [cos,0] is cos 0
and I want to write the set of rules that finds the numeric value of a mathematical expression written by this language in prolog.
I first wrote a function called "check", it checks to see if the list is written in a right way according to the language we have :
check1([]).
check1([L|Ls]):- number(L),check1(Ls).
check([L|Ls]):-atom(L),check1(Ls).
now I need to write the function "evaluate" that takes a list that is an expression written by this language, and a variable that is the numeric value corresponding to this language.
example:
?-evaluate([*,1,[^,2,2],[*,2,[+,[sin,0],5]]]],N) -> N = 40
so I wrote this:
sum([],0).
sum([L|Ls],N):- not(is_list(L)),sum(Ls,No),N is No + L.
min([],0).
min([L|Ls],N):-not(is_list(L)), min(Ls,No),N is No - L.
pro([],0).
pro([X],[X]).
pro([L|Ls],N):-not(is_list(L)), pro(Ls,No), N is No * L.
pow([L|Ls],N):-not(is_list(L)), N is L ^ Ls.
sin_(L,N):-not(is_list(L)), N is sin(L).
cos_(L,N):-not(is_list(L)), N is cos(L).
d([],0).
d([L|Ls],N):- L == '+' ,sum(Ls,N);
L == '-',min(Ls,N);
L == '*',pro(Ls,N);
L == '^',pow(Ls,N);
L == 'sin',sin_(Ls,N);
L == 'cos',cos_(Ls,N).
evaluate([],0).
evaluate([L|Ls],N):-
is_list(L) , check(L) , d(L,N),L is N,evaluate(Ls,N);
is_list(L), not(check(L)) , evaluate(Ls,N);
not(is_list(L)),not(is_list(Ls)),check([L|Ls]),d([L|Ls],N),
L is N,evaluate(Ls,N);
is_list(Ls),evaluate(Ls,N).
and it's working for just a list and returning the right answer , but not for multiple lists inside the main list, how should my code be?
The specification you work with looks like a production rule that describes that E (presumably short for Expression) might be a number or one of the 6 specified operations. That is the empty list [] is not an expression. So the fact
evaluate([],0).
should not be in your code. Your predicate sum/2 almost works the way you wrote it, except for the empty list and a list with a single element, that are not valid inputs according to your specification. But the predicates min/2 and pro/2 are not correct. Consider the following examples:
?- sum([1,2,3],X).
X = 6 % <- correct
?- sum([1],X).
X = 1 % <- incorrect
?- sum([],X).
X = 0 % <- incorrect
?- min([1,2,3],X).
X = -6 % <- incorrect
?- pro([1,2,3],X).
X = 6 ? ; % <- correct
X = 0 % <- incorrect
Mathematically speaking, addition and multiplication are associative but subtraction is not. In programming languages all three of these operations are usually left associative (see e.g. Operator associativity) to yield the mathematically correct result. That is, the sequence of subtractions in the above query would be calculated:
1-2-3 = (1-2)-3 = -4
The way you define a sequence of these operations resembles the following calculation:
[A,B,C]: ((0 op C) op B) op A
That works out fine for addition:
[1,2,3]: ((0 + 3) + 2) + 1 = 6
But it doesn't for subtraction:
[1,2,3]: ((0 - 3) - 2) - 1 = -6
And it is responsible for the second, incorrect solution when multiplying:
[1,2,3]: ((0 * 3) * 2) * 1 = 0
There are also some other issues with your code (see e.g. #lurker's comments), however, I won't go into further detail on that. Instead, I suggest a predicate that adheres closely to the specifying production rule. Since the grammar is describing expressions and you want to know the corresponding values, let's call it expr_val/2. Now let's describe top-down what an expression can be: It can be a number:
expr_val(X,X) :-
number(X).
It can be an arbitrarily long sequence of additions or subtractions or multiplications respectively. For the reasons above all three sequences should be evaluated in a left associative way. So it's tempting to use one rule for all of them:
expr_val([Op|Es],V) :-
sequenceoperator(Op), % Op is one of the 3 operations
exprseq_op_val(Es,Op,V). % V is the result of a sequence of Ops
The power function is given as a list with three elements, the first being ^ and the others being expressions. So that rule is pretty straightforward:
expr_val([^,E1,E2],V) :-
expr_val(E1,V1),
expr_val(E2,V2),
V is V1^V2.
The expressions for sine and cosine are both lists with two elements, the first being sin or cos and the second being an expression. Note that the argument of sin and cos is the angle in radians. If the second argument of the list yields the angle in radians you can use sin/1 and cos/2 as you did in your code. However, if you get the angle in degrees, you need to convert it to radians first. I include the latter case as an example, use the one that fits your application.
expr_val([sin,E],V) :-
expr_val(E,V1),
V is sin(V1*pi/180). % radians = degrees*pi/180
expr_val([cos,E],V) :-
expr_val(E,V1),
V is cos(V1*pi/180). % radians = degrees*pi/180
For the second rule of expr_val/2 you need to define the three possible sequence operators:
sequenceoperator(+).
sequenceoperator(-).
sequenceoperator(*).
And subsequently the predicate exprseq_op_val/3. As the leading operator has already been removed from the list in expr_val/2, the list has to have at least two elements according to your specification. In order to evaluate the sequence in a left associative way the value of the head of the list is passed as an accumulator to another predicate exprseq_op_val_/4
exprseq_op_val([E1,E2|Es],Op,V) :-
expr_val(E1,V1),
exprseq_op_val_([E2|Es],Op,V,V1).
that is describing the actual evaluation. There are basically two cases: If the list is empty then, regardless of the operator, the accumulator holds the result. Otherwise the list has at least one element. In that case another predicate, op_val_args/4, delivers the result of the respective operation (Acc1) that is then recursively passed as an accumulator to exprseq_op_val_/4 alongside with the tail of the list (Es):
exprseq_op_val_([],_Op,V,V).
exprseq_op_val_([E1|Es],Op,V,Acc0) :-
expr_val(E1,V1),
op_val_args(Op,Acc1,Acc0,V1),
exprseq_op_val_(Es,Op,V,Acc1).
At last you have to define op_val_args/4, that is again pretty straightforward:
op_val_args(+,V,V1,V2) :-
V is V1+V2.
op_val_args(-,V,V1,V2) :-
V is V1-V2.
op_val_args(*,V,V1,V2) :-
V is V1*V2.
Now let's see how this works. First your example query:
?- expr_val([*,1,[^,2,2],[*,2,[+,[sin,0],5]]],V).
V = 40.0 ? ;
no
The simplest expression according to your specification is a number:
?- expr_val(-3.14,V).
V = -3.14 ? ;
no
The empty list is not an expression:
?- expr_val([],V).
no
The operators +, - and * need at least 2 arguments:
?- expr_val([-],V).
no
?- expr_val([+,1],V).
no
?- expr_val([*,1,2],V).
V = 2 ? ;
no
?- expr_val([-,1,2,3],V).
V = -4 ? ;
no
The power function has exactly two arguments:
?- expr_val([^,1,2,3],V).
no
?- expr_val([^,2,3],V).
V = 8 ? ;
no
?- expr_val([^,2],V).
no
?- expr_val([^],V).
no
And so on...

Determine if number is prime in Prolog

So I'm trying to determine if a number is prime using only one predicate. I don't really understand why every number is being declared false here.
is_prime(2).
is_prime(X) :-
X > 2, %0 and 1 aren't primes, 2 is dealt with above
1 is mod(X,2), %number is odd
N is floor(X/2), %I want to only divide X from 1 to X/2
forall( between(1,N,Z), mod(X,Z) > 0 ). %This should do X mod 1:X/2
The reason your code don't work is the start value of between/3: It should start with 2 (not 1), since X mod 1 is always 0.
A very straight-forward solution uses CLP(FD) constraints to express the desired properties.
We start with a simpler predicate, which is true iff the number is composite:
is_composite(N) :-
N #= A*B,
[A,B] ins 2..sup.
The exact usage details for CLP(FD) constraints differ slightly between Prolog systems. With at most small modifications, you will be able to run the above in all most widely used systems.
Done!
Because:
A prime number is an integer greater than 1 that is not composite.
Here are a few examples:
?- length([_,_|_], P), \+ is_composite(P).
P = 2 ;
P = 3 ;
P = 5 ;
P = 7 ;
P = 11 ;
P = 13 ;
P = 17 ;
P = 19 ;
P = 23 ;
P = 29 ;
etc.
In general, it is good practice to use CLP(FD) constraints when reasoning over integers in Prolog.

Generating integers < limit

I am trying to generate all integers (natural numbers) smaller than a limit, let's say 10.
I have a predicate nat(X) which produces all numbers from 0 to infinity.
Now my problem is, if I do:
nat10(X) :- nat(X), X =< 10.
This will never terminate, as it tries to find other solutions with nat(X) until infinity.
I need a construct that let's me fail the whole predicate if one subgoal fails. How would I go about doing that?
Depending upon the problem being solved, you might want to consider constraint logic programming over finite domains (CLPFD).
But in this context, you need just prevent Prolog from backtracking if X > 10. The current predicate nat10/1 has no such constraint, so we'll add it:
nat10(X) :- nat(X), ( X > 10 -> !, fail ; true ).
So if X > 10, we do a cut (!) to prevent backtracking to nat(X) (thus avoiding generating natural numbers above 10 infinitely) and then simply fail. Otherwise, we succeed (true).
| ?- nat10(X).
X = 1 ? ;
X = 2 ? ;
...
X = 9 ? ;
X = 10 ? ;
(3 ms) no
| ?-
If you can use clpfd, then this answer is for you!
:- use_module(library(clpfd)).
Simply try:
nat10(X) :-
X in 0..10,
indomain(X).

How to Print numbers from 1 to 100 in Prolog?

The following code is a Prolog code which gives all integers greater than 0. Each time i put ; in the interpreter, it gives the next number:
is_integer(0).
is_integer(X) :- is_integer(Y),X is Y+1.
Is there a way where it gives numbers between 0 and 100 only. When it reaches 100 it should stop.
There is a built-in predicate between/3 for that purpose in B, Ciao, SICStus (library), SWI, YAP, XSB (library).
?- between(0,100,X).
X = 0
; X = 1
; ...
; X = 100.
If you start to learn Prolog, better try to use s(X) numbers first which are much easier to understand and reason about. The same example, but only going up to 3:
?- nat_nat_sum(N,_,s(s(s(0)))).
with the definition:
nat_nat_sum(0,I,I).
nat_nat_sum(s(I),J,s(K)) :-
nat_nat_sum(I,J,K).
What a nice quiz. It exemplifies very well how difficult can be to control the recursion with the minimal tools that Prolog defines. We must commit our solutions to values lower than the predefined limit, restricting the otherless unbound search:
is_integer(0).
is_integer(X) :-
is_integer(Y),
( Y >= 100, ! ; X is Y + 1 ).
Here is the trace output limiting the range to 3 (i.e. ... Y >= 3, ! ; ...)
?- is_integer(X).
X = 0 ;
X = 1 ;
X = 2 ;
X = 3 ;
true.

Resources