Defining a mathematical language in prolog - 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...

Related

Prolog find the element with the max number of occurrences

I would like to create a predicate that returns the element that most often appears, if there are more than one with the same number of occurrences the first:
occ([a,b,c,a,a,a,b],M).
yes M = a
occ([a,b,c,a,b],M).
yes M = a
Note that in Prolog you would generally create rules, not functions to solve this.
There are a number of ways to approach this, I'll provide two.
Recursion
One way is to recurse over the list, keeping a running count of occurrences, and with each call recording what the current max is, an example of use of an accumulator:
% find the X with the most occurrences N in a list L
occ(X,N,L) :-
occ(L,max(null,0),[],max(X,N)).
%% occ(+L, +CurrentMax, +Counts, +FinalMax) is det.
%
% recurse through L, using CurrentMax accumulator to
% store current candidate as a term `max(X,N)`
%
% Counts is a list in which we accumulate counts of
% occurrences to far, as list of element-count pairs X-N
%
% The final argument is unified with the CurrentMax
% accumulator as the base case
occ([], max(Xm, Nm), _, max(Xm, Nm)).
occ([X|L], max(Xm, Nm), Counts, FinalMax) :-
% get the current count of X
( select(X-N, Counts, CountsT)
->
N1 is N+1
;
N1 = 1,
CountsT = Counts),
% make a new list of counts with the
% original entry for X replaced by a new
% one with count of N+1
Counts2 = [X-N1 | CountsT],
% recurse, using either new current best candidate
% or same one depending on whether count is exceeded.
% in case of tie, use same one, thus prioritizing first result
( N1 > Nm
->
occ(L, max(X,N1), Counts2, FinalMax)
;
occ(L, max(Xm,Nm), Counts2, FinalMax)).
Example:
?- occ(X,N,[a,b,c,a,b]).
X = a,
N = 2.
Higher-order aggregate operations
An alternative approach is to use higher-order aggregate predicates. Arguably this leads to more declarative code, although tastes will vary. If you are using SWI-Prolog you can use the aggregate library. We can start with a rule to count occurrences in a list (note I'm going to switch from your occ/2 to more explicit predicates here):
% count number N of instances of X in a list L
element_count(X,N,L) :-
aggregate(count,member(X,L),N).
If you don't want to or can't use aggregate/3 then have a look at the answers to this question previously asked on stack overflow.
Next we can use aggregate/3 to find the maximum number for N, plus a "witness" (i.e. the value of X with the highest value):
% count number N of instances of X in a list L, for highest N
max_element_count(X,N,L) :-
aggregate(max(N1,X1),element_count(X1,N1,L),max(N,X)).
(I'll leave it to you to make an equivalent implementation of this rule if you're not using the aggregate library)
Let's try it:
?- max_element_count(X,N,[a,b,c,a,a,a,b]).
X = a,
N = 4.
With a tie it seems to satisfy your criterion of using the first occurrence in the case of tie-breakers:
?- max_element_count(X,N,[a,b,c,a,b]).
X = a,
N = 2.
But this is not in fact guaranteed - we just happen to choose a here as it is alphabetically before b. Let's try:
?- max_element_count(X,N,[b,a,c,a,b]).
X = a,
N = 2.
Oops!
This time we will find the first member of the list whose number of occurrences is equal to the max:
max_element_count2(X,N,L) :-
aggregate(max(N1),X1,element_count(X1,N1,L),N),
member(X,L),
element_count(X,N,L),
!.
This assumes that member/2 will unify with elements in order, which is the behavior I have always seen with Prologs but don't know off the top of my head if it is mandated by the standard.
To demonstrate:
?- max_element_count2(X,N,[b,a,c,a,b]).
X = b,
N = 2.

Finding consistent assignments for logical formulas

I am about to implement a prover for logical terms in Prolog. My current code is not really presentable, therefore, I will just state, what I want my program to do and hopefully you can give me some good advice for that :)
It should take a list of variables (so to say the logical arguments) and secondly a logical formula containing these arguments (e.g. 'not'(A 'and' B) 'or' 'not'(B 'and' C) 'or' ... and so forth).
As output I would like my program to respond with the possible consistent assignments. The single arguments can either be true (1) or false (0).
So I aim for a return like A=0, B=0, C=0 ; A=1 and so forth.
I am happy for every help concerning my program :)
There are several ways one could approach this. One way that is convenient in terms of syntax would be to define operators, something like this:
:- op(500, fx, not).
:- op(600, xfx, and).
:- op(700, xfx, or).
(I am just guessing at reasonable precedence settings here, but just for illustration. See the op documentation for details.)
Having done that, you can write an expression such as: A and B and Prolog will "see" it as and(A, B):
| ?- write_canonical(A and B).
and(_23,_24)
From there, you need to have a way to evaluate an expression. There are lots of questions on SO here in this regard (do a search in this site on [prolog] boolean expression evaluation), but I'll provide a simple example. It's now all about how you want to represent a result, and about recursion.
When it comes to representing a result, you could use Prolog's success/fail mechanism since you are dealing with boolean results. Or, you can have an explicit result, such as 0 and 1. Let's try 0 and 1 since that's your representation for true and false.
% Describe a valid boolean
bool(0).
bool(1).
% The evaluation of a valid boolean is itself
exp_eval(X, X) :- bool(X).
% Evaluation of an 'and' expression
exp_eval(and(A, B), Result) :-
exp_eval(A, ResultA),
exp_eval(B, ResultB),
Result #= ResultA * ResultB.
% Evaluation of an 'or' expression
exp_eval(or(A, B), Result) :-
exp_eval(A, ResultA),
exp_eval(B, ResultB),
% Just a little trick to get 1 if either ResultA or ResultB or both are 1
Result #= (ResultA + ResultB + 1) // 2.
% Evaluation of a 'not' expression
exp_eval(not(A), Result) :-
exp_eval(A, ResultNot),
Result #= 1 - ResultNot. % 0 ---> 1, and 1 ---> 0
Instead of calculating "boolean" 1/0 results as I've done above, you could, instead, assert them as facts like so:
bool_not(0, 1).
bool_not(1, 0).
bool_and(0, 0, 0).
bool_and(0, 1, 0).
bool_and(1, 0, 0).
bool_and(1, 1, 1).
bool_or(0, 0, 0).
bool_or(0, 1, 1).
bool_or(1, 0, 1).
bool_or(1, 1, 1).
And then, for example, instead of Result #= (ResultA + ResultB + 1) // 2 you could just have, bool_or(ResultA, ResultB, Result).
Now that we can evaluate expressions, we want a solver:
solve(Exp) :-
term_variables(Exp, Variables),
maplist(bool, Variables), % Variables should be valid booleans
exp_eval(Exp, 1). % We only want true results for the expression
Note that in the original problem statement, it's said that the variable list would be given as an argument, but you can use term_variables/2 to obtain the variables from an expression.
Then you can run the solver:
| ?- solve(not(A and B) or not(B and C)).
A = 0
B = 0
C = 0 ? a
A = 0
B = 0
C = 1
A = 0
B = 1
C = 0
A = 0
B = 1
C = 1
A = 1
B = 0
C = 0
A = 1
B = 0
C = 1
A = 1
B = 1
C = 0
no
| ?-
I don't know what your representation is for an expression. But whatever it is, you can map it to the above solution. What I've shown is simple and clear. You could skip the op/3 stuff and use standard term expressions, like, or(not(and(A,B)), not(and(B,C))) using the above code. If you have your input as some kind of token sequence, like, [not, (, A, and, B, ...] then you'll have to do a little list processing.

Sum of the first n numbers in prolog

Hello can anyone help me compute the sum of the first n numbers. For example n=4 => sum = 10.
So far I've wrote this
predicates
sum(integer,integer)
clauses
sum(0,0).
sum(N,R):-
N1=N-1,
sum(N1,R1),
R=R1+N.
This one works but I need another implementation. I don't have any ideas how I could make this differen . Please help
What #mbratch said.
What you're computing is a triangular number. If your homework is about triangular numbers and not about learning recursive thinking, you can simply compute it thus:
triangular_number(N,R) :- R is N * (N+1) / 2 .
If, as is more likely, you're learning recursive thought, try this:
sum(N,R) :- % to compute the triangular number n,
sum(N,1,0,R) % - invoke the worker predicate with its counter and accumulator properly seeded
.
sum(0,_,R,R). % when the count gets decremented to zero, we're done. Unify the accumulator with the result.
sum(C,X,T,R) :- % otherwise,
C > 0 , % - assuming the count is greater than zero
T1 is T+X , % - increment the accumulator
X1 is X+1 , % - increment the current number
C1 is C-1 , % - decrement the count
sum(C1,X1,T1,R) % - recurse down
. % Easy!
Edited to add:
Or, if you prefer a count down approach:
sum(N,R) :- sum(N,0,R).
sum(0,R,R). % when the count gets decremented to zero, we're done. Unify the accumulator with the result.
sum(N,T,R) :- % otherwise,
N > 0 , % - assuming the count is greater than zero
T1 is T+N , % - increment the accumulator
N1 is N-1 , % - decrement the count
sum(N1,T1,R) % - recurse down
. % Easy!
Both of these are tail-recursive, meaning that the prolog compiler can turn them into iteration (google "tail recursion optimization" for details).
If you want to eliminate the accumulator, you need to do something like this:
sum(0,0).
sum(N,R) :-
N > 0 ,
N1 is N-1 ,
sum(N1,R1) ,
R is R1+N
.
A little bit simpler, but each recursion consumes another stack frame: given a sufficiently large value for N, execution will fail with a stack overflow.
sum(N, Sum) :-
Sum is (N + 1) * N / 2 .
Since you already got plenty of advice about your code, let me throw in a snippet (a bit off-topic).
Counting, and more generally, aggregating, it's an area where Prolog doesn't shine when compared to other relational,declarative languages (read SQL). But some vendor specific library make it much more pleasant:
?- aggregate(sum(N),between(1,4,N),S).
S = 10.
This is the "heart" of your program:
sum(N,R):-
R=R+N,
N=N-1,
sum(N,R).
The =/2 predicate (note the /2 means it accepts 2 arguments) is the instantiation predicate, not an assignment, or logical equal. It attempts to unify its arguments to make them the same. So if N is anything but 0, then R=R+N will always fail because R can never be the same as R+N. Likewise for N=N-1: it will always fail because N and N-1 can never be the same.
In the case of =/2 (unification), expressions are not evaluated. They are just terms. So if Y = 1, then X = Y + 1 unifies X with 1+1 as a term (equivalently written +(1,1)).
Because of the above issues, sum will always fail.
Numerical assignment of an arithmetic expression is done in Prolog with the is/2 predicate. Like this:
X is Y + 1.
This operator unifies the value of X to be the same as the value of the evaluated expression Y+1. In this case, you also cannot have X is X+1 for the same reason given above: X cannot be made the same as X+1 and Prolog does not allow "re-instantiation" of a variable inside of a clause. So you would need something like, X1 is X + 1. Also note that for is/2 to work, everything in the expression on the right must be previously instantiated. If any variables in the expression on the right do not have a value, you will get an instantiation error or, in the case of Turbo Prolog, Free variable in expression....
So you need to use different variables for expression results, and organize the code so that, if using is/2, variables in the expression are instantiated.
EDIT
I understand from Sergey Dymchenko that Turbo Prolog, unlike GNU or SWI, evaluates expressions for =/2. So the = will work in the given problem. However, the error regarding instantiation (or "free variable") is still caused by the same issue I mentioned above.
sum(N, N, N).
sum(M, N, S):-
N>M,
X is M+1,
sum(X, N, T),
S is M+T.
?- sum(1,5,N).
N = 15 .

Evaluating an algebraic expression

This is a test review question that I am having trouble with. How do you write a method to evaluate an algebraic expression with the operators plus,
minus and times. Here are some test queries:
simplify(Expression, Result, List)
?- simplify(plus(times(x,y),times(3 ,minus(x,y))),V,[x:4,y:2]).
V = 14
?- simplify(times(2,plus(a,b)),Val,[a:1,b:5]).
Val = 12
?- simplify(times(2,plus(a,b)),Val,[a:1,b:(-5)]).
Val = -8 .
All I was given were these sample queries and no other explanation. But I am pretty sure the method is supposed to dissect the first argument, which is the algebraic expression, substituting x and y for their values in the 3rd argument (List). The second argument should be the result after evaluating the expression.
I think one of the methods should be simplify(V, Val, L) :- member(V:Val, L).
Ideally there should only be 4 more methods... but I'm not sure how to go about this.
Start small, write down what you know.
simplify(plus(times(x,y),times(3 ,minus(x,y))),V,[x:4,y:2]):- V = 14.
is a perfectly good start: (+ (* 4 2) (* 3 (- 4 2))) = 8 + 3*2 = 14. But then, of course,
simplify(times(x,y),V,[x:4,y:2]):- V is 4*2.
is even better. Also,
simplify(minus(x,y),V,[x:4,y:2]):- V is 4-2.
simplify(plus(x,y),V,[x:4,y:2]):- V is 4+2.
simplify(x,V,[x:4,y:2]):- V is 4.
all perfectly good Prolog code. But of course what we really mean, it becomes apparent, is
simplify(A,V,L):- atom(A), getVal(A,L,V).
simplify(C,V,L):- compound(C), C =.. [F|T],
maplist( simp(L), T, VS), % get the values of subterms
calculate( F, VS, V). % calculate the final result
simp(L,A,V):- simplify(A,V,L). % just a different args order
etc. getVal/3 will need to retrieve the values somehow from the L list, and calculate/3 to actually perform the calculation, given a symbolic operation name and the list of calculated values.
Study maplist/3 and =../2.
(not finished, not tested).
OK, maplist was an overkill, as was =..: all your terms will probably be of the form op(A,B). So the definition can be simplified to
simplify(plus(A,B),V,L):-
simplify(A,V1,L),
simplify(B,V2,L),
V is V1 + V2. % we add, for plus
simplify(minus(A,B),V,L):-
% fill in the blanks
.....
V is V1 - V2. % we subtract, for minus
simplify(times(A,B),V,L):-
% fill in the blanks
.....
V is .... . % for times we ...
simplify(A,V,L):-
number(A),
V = .... . % if A is a number, then the answer is ...
and the last possibility is, x or y etc., that satisfy atom/1.
simplify(A,V,L):-
atom(A),
retrieve(A,V,L).
So the last call from the above clause could look like retrieve(x,V,[x:4, y:3]), or it could look like retrieve(y,V,[x:4, y:3]). It should be a straightforward affair to implement.

Categorise List in Prolog

Alright so I am coding a parser for arithmetic equations. I get the input in a list, e.g. "10+20" = [49,48,43,50,48] and then I convert all the digits to there corresponding numbers e.g. [49,48,43,50,48] = [1,0,43,2,0] and from there I want to put integers > 10 back together.
Converting from ascii -> digits I use a maplist and number_codes to convert.
One approach I had was to just traverse the list and if it's 0-9 store it in a variable and then check the next number, 0-9 append it to the other variable and so on until I hit an operator. I can't seem to simply append digits as it were. Here's my current code.
expression(L) :-
maplist(chars, L, Ls).
chars(C, N) :-
(
C >= "0", "9" >= C -> number_codes(N, [C]);
N is C
).
Not sure if there's a simple way to add to my code (as far as I know, maplist only gives back a list of equal length to the list passed in but I could be mistaken).
Any help is appreciated :)
Yes, maplist only 'gives back' a list of equal length. Moreover, maplist applies a predicate only to one element (basically it's context-free). Therefore, it is not possible to do what you want (combine digits between operators to a single number) with maplist and you would have to write the recursion yourself.
However, you can do something way easier than all this converting back and forth:
expression(L, E):-
string_to_atom(L,A),
atom_to_term(A,E,[]).
Which works like this:
2 ?- expression("1+2",E).
E = 1+2.
3 ?- expression("1+2",E), X is E.
E = 1+2, X = 3.
4 ?- expression("1+2",E), X+Y = E.
E = 1+2, X = 1, Y = 2.
5 ?- expression("1+2+3",E), X+Y = E.
E = 1+2+3, X = 1+2, Y = 3.
Naturally, if you want a list with all the numbers involved you will have to do something recursive but this is kinda trivial imho.
If however you still want to do the converting, I suggest checking Definite Clause Grammars; it will simplify the task a lot.
I answered some time ago with an expression parser.
It will show you how to use DCG for practical tasks, and I hope you will appreciate the generality and simplicity of such approach.
Just a library predicate is required from SWI-Prolog, number//1, easily implemented in Sicstus. Let me know if you need more help on that.

Resources