This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
polynomialmani.pl/polymani.pl

1492 lines
41 KiB
Prolog

%% -*- Mode: Prolog-*-
%% vim: set softtabstop=4 shiftwidth=4 tabstop=4 expandtab:
/**
*
* polimani.pl
*
* Assignment 1 - Polynomial Manipulator
* Programming in Logic - DCC-FCUP
*
* Diogo Peralta Cordeiro
* up201705417@fc.up.pt
*
* Hugo David Cordeiro Sales
* up201704178@fc.up.pt
*
*********************************************
* Follows 'Coding guidelines for Prolog' *
* https://doi.org/10.1017/S1471068411000391 *
*********************************************/
/*
* Import the Constraint Logic Programming over Finite Domains library
* Essentially, this library improves the way Prolog deals with integers,
* allowing more predicates to be reversible.
* For instance, number(N) is always false, which prevents the
* reversing of a predicate.
*/
:- use_module(library(clpfd)).
/*
* Import Constraint Logic Programming for Reals library, which is somewhat
* similar to clpfd, but for real numbers
*/
:- use_module(library(clpr)).
/*******************************
* NLP *
*******************************/
%% polyplay() is det
%
% Interactive prompt for the NLP Interface
%
polyplay :-
%% Replace the prompt and save the old one
prompt(OldPrompt, '> '),
%% Read a line as codes, from the 'user_input' stream
read_line_to_codes(user_input, InCodes),
prompt(_, OldPrompt),
split_string(InCodes, " ", "\r\t", LS),
maplist(name, LA, LS),
(
LA == [bye],
write("See ya"),
nl,
!
;
(
parse_input(TIn, LA, NC),
(
TIn == void,
writeln("I didn't understand what you want."),
writeln(NC)
;
(
NC \== [],
write("Syntax error in token: "),
cons(H, _, NC),
write(H),
nl
;
(
debug_print(true),
write(LA),
nl,
write(TIn),
nl
;
process_input(TIn)
)
)
)
;
writeln("I didn't understand what you want.")
),
polyplay
),
!.
%% Flag which determines whether to print the parsed input or to process it
debug_print(false).
process_input(command(CL, void)) :-
do_process_input(CL).
process_input(command(CL, TCR)) :-
%% Process first command
do_process_input(CL),
%% If there's a tree on the right
TCR \== void,
%% recurse
process_input(TCR).
do_process_input(help_menu) :-
writeln("Please allow me to introduce myself"),
writeln("I'm a man[ual] of wealth and taste"),
writeln("I've been around for a long, long semester"),
writeln("Saved many a man's soul and faith"),
writeln("Pleased to meet you"),
writeln("Hope you guess my name"),
writeln("But what's puzzling you"),
writeln("Is the nature of my game"),
nl,
writeln("I'm a Polynomial Manipulator and the following commands are available:"),
writeln("=> Show - Allows to print a polynomial mathematically"),
writeln("=> Multiply - Allows to make multiplications"),
writeln("=> Simplify - Allows to simplify a given polynomial"),
writeln("=> Add - Allows to make sums"),
writeln("=> bye - Hello darkness, my old friend"),
writeln("Use 'tell me about {command}' to learn more about a specific command"),
nl,
writeln("Furthermore, I'm capable of memorizing polynomials during runtime. To learn more on that, type: tell me about storage").
do_process_input(help(show)) :-
writeln("It's almost an echo of what you said, but a mathy one."),
writeln("Some example queries:"),
writeln(">").
do_process_input(help(multiply)) :-
writeln("Multiplies a polynomial represented as an expression by a scalar resulting in a second polynomial. The two first arguments are assumed to be ground. The polynomial resulting from the sum is in simplified form."),
writeln("Some example queries:"),
writeln(">").
do_process_input(help(simplify)) :-
writeln("Simplifies a polynomial represented as an expression as another polynomial as an expression."),
writeln("Some example queries:"),
writeln(">").
do_process_input(help(add)) :-
writeln("Adds two polynomials as expressions resulting in a third one. The two first arguments are assumed to be ground. The polynomial resulting from the sum is in simplified form."),
writeln("Some example queries:"),
writeln(">").
do_process_input(help(storage)) :-
writeln("Polynomials, pressed between the entries of my storage"),
writeln("Polynomials, simplified through the ages just like predicates"),
writeln("Quiet goal come floating down"),
writeln("And settle softly to the ground"),
writeln("Like golden atom leaves around my root"),
writeln("I touched them and they burst apart with sweet polynomials"),
writeln("Sweet polynomials"),
nl,
writeln("Storage manipulation is better illustrated with examples. Some example queries:"),
writeln("Asking me to memorize something:"),
writeln(">"),
nl,
writeln("Asking me to forget something:"),
writeln(">"),
nl,
writeln("Some examples of memory resources usage:"),
writeln(">").
do_process_input(help(bye)) :-
writeln("There must be some kind of way outta here"),
writeln("Said the joker to the thief"),
writeln("There's too much confusion"),
writeln("I can't get no relief").
do_process_input(show_stored_polynomials) :-
findall(nm(X,Y), polynomial_store(X,Y), D),
print_all_stored_variables(D).
do_process_input(show(store(P), T)) :-
( polynomial_store(P, _),
retractall(polynomial_store(P, _)); true ),
!,
assertz(polynomial_store(P, T)),
write(P),
write(" = "),
polynomial_tree_to_polynomial(T, Pl),
write(Pl),
nl.
do_process_input(show(load(P), void)) :-
P \== void,
(
polynomial_store(P, T),
write(P),
write(" = "),
polynomial_tree_to_polynomial(T, Pl),
write(Pl),
nl
;
write("Variable not stored"),
nl
).
do_process_input(show(P, T)) :-
P \== void,
P \== store(_),
T \== void,
write(P),
write(" = "),
polynomial_tree_to_polynomial(T, Pl),
write(Pl),
nl.
do_process_input(show(void, T)) :-
T \== void,
polynomial_tree_to_polynomial(T, Pl),
write(Pl),
nl.
do_process_input(store(P, T)) :-
assertz(polynomial_store(P, T)).
do_process_input(forget(P)) :-
retract(polynomial_store(P, _)).
do_process_input(simplify(PT)) :-
polynomial_tree_to_polynomial(PT, P),
simpoly(P, SP),
write(SP),
nl.
do_process_input(multiply(TN, PT)) :-
polynomial_tree_to_polynomial(TN, N),
polynomial_tree_to_polynomial(PT, P),
(
not(number(N)),
scalepoly(N, P, P2)
;
number(N),
scalepoly(P, N, P2)
),
simpoly(P2, SP),
write(SP),
nl.
%% print_all_stored_variables
%
% Prints the stored variables
%
print_all_stored_variables([nm(X,T) | TS]) :-
write(X),
write(" = "),
polynomial_tree_to_polynomial(T, P),
write(P),
nl,
print_all_stored_variables(TS).
print_all_stored_variables([]).
polynomial_tree_to_polynomial(op(Op, TL, TR), P) :-
!,
polynomial_tree_to_polynomial(TL, PL),
polynomial_tree_to_polynomial(TR, PR),
term_to_atom(PL, TermL),
term_to_atom(PR, TermR),
atom_concat(TermL, Op, Temp),
atom_concat(Temp, TermR, PA),
term_to_atom(P, PA).
polynomial_tree_to_polynomial(load(P), Pl) :-
polynomial_store(P, TP),
polynomial_tree_to_polynomial(TP, Pl).
polynomial_tree_to_polynomial(T, T).
%% Tests:
%% ?- polynomial_tree_to_polynomial(op(+, 2, op(+, 2, op(*, 1, y))), S).
%@ S = 2+2+1*y.
%% nlp_number(?W:Atom, ?D:Int) is det
%
% Definition of a Alphabetical and Numerical relation
%
special_word_number(zero, 0, f).
special_word_number(a, 1, f).
special_word_number(one, 1, f).
special_word_number(two, 2, f).
special_word_number(three, 3, f).
special_word_number(four, 4, f).
special_word_number(five, 5, f).
special_word_number(six, 6, f).
special_word_number(seven, 7, f).
special_word_number(eight, 8, f).
special_word_number(nine, 9, f).
special_word_number(ten, 10, g).
special_word_number(eleven, 11, g).
special_word_number(twelve, 12, g).
special_word_number(thirteen, 13, g).
special_word_number(fourteen, 14, g).
special_word_number(fifteen, 15, g).
special_word_number(sixteen, 16, g).
special_word_number(seventeen, 17, g).
special_word_number(eighteen, 18, g).
special_word_number(nineteen, 19, g).
special_word_number(twenty, 20, fy).
special_word_number(thirty, 30, fy).
special_word_number(forty, 40, fy).
special_word_number(fifty, 50, fy).
special_word_number(sixty, 60, fy).
special_word_number(seventy, 70, fy).
special_word_number(eighty, 80, fy).
special_word_number(ninety, 90, fy).
special_word_number(hundred, 100, xfy).
special_word_number(thousand, 1000, xfy).
special_word_number(million, 1000000, xfy).
%% special_word_number(half, 0.5, xf).
%% special_word_number(third, 0.33333, xf).
%% special_word_number(quarter, 0.25, xf).
%% nlp_number(?W:Atom, ?D:Int) is det
%
% Definition of a Alphabetical and Numerical relation
%
%% Entry point
parse_number_explicit(void, void, T, [WN | In], NC) :-
special_word_number(WN, N, P),
member(P, [f, g, fy]),
!,
parse_number_explicit(P, N, T, In, NC).
parse_number_explicit(fy, NL, T, [WN | In], NC) :-
special_word_number(WN, N, f),
!,
parse_number_explicit(f, op(-, NL, N), T, In, NC).
parse_number_explicit(fy, NL, T, [WN | In], NC) :-
special_word_number(WN, N, f),
!,
parse_number_explicit(f, op(+, NL, N), T, In, NC).
parse_number_explicit(xfy, TL, T, [WN | In], NC) :-
TL \= void,
special_word_number(WN, N, P),
member(P, [f, g, fy]),
!,
parse_number_explicit(P, op(-, TL, N), T, In, NC).
parse_number_explicit(xfy, TL, T, [WN | In], NC) :-
TL \= void,
special_word_number(WN, N, P),
member(P, [f, g, fy]),
!,
parse_number_explicit(P, op(+, TL, N), T, In, NC).
parse_number_explicit(_, TL, T, [WN | In], NC) :-
special_word_number(WN, N, xfy),
TL \= void,
!,
parse_number_explicit(xfy, op(*, TL, N), T, In, NC).
parse_number_explicit(P, TL, T, [and, WN | In], NC) :-
special_word_number(WN, _, _),
parse_number_explicit(P, TL, T, [WN | In], NC),
!.
parse_number_explicit(_, T, T, [WN | In], [WN | In]) :-
T \= void,
not(special_word_number(WN, _, _)),
!.
parse_number_explicit(_, T, T, [], []) :-
T \= void,
!.
parse_number(op('.', TL, TR)) -->
parse_number_explicit(void, void, TL),
[X],
{ member(X, [point, dot]), ! },
parse_number_explicit(void, void, TR).
parse_number(N) -->
[N],
{ number(N), ! }.
parse_number(T) -->
parse_number_explicit(void, void, T).
%% NOTE This is not supposed to be here.
%% polynomial_tree_to_polynomial(T1, PP),
%% simpoly(PP, T2).
%% Tests:
%% ?- parse_number(T, [two], _).
%@ T = 2.
%% ?- parse_number(T, [43], _).
%@ T = 43.
%% ?- parse_number(T, [nineteen, two], _).
%@ false.
%% ?- parse_number(T, [twenty], _).
%@ T = 20.
%% ?- parse_number(T, [twenty, point, two], NC).
%@ T = op('.', 20, 2),
%@ NC = [].
%% ?- parse_number(T, [twenty, twenty], _).
%@ false.
%% ?- parse_number(T, [twenty, one], _).
%@ T = op(+, 20, 1).
%% ?- parse_number(T, [hundred], _).
%@ false.
%% ?- parse_number(T, [three, hundred], _).
%@ T = op(*, 3, 100).
%% ?- parse_number(T, [twenty, hundred], _).
%@ T = op(*, 20, 100).
%% ?- parse_number(T, [twenty, one, hundred], _).
%@ T = op(*, op(+, 20, 1), 100).
%% ?- parse_number(T, [two, hundred, and, one], _).
%@ T = op(+, op(*, 2, 100), 1).
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one], _).
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1).
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one, foo, bar, blah], NC).
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1),
%@ NC = [foo, bar, blah].
%% ?- parse_number(T, [twenty, one, hundred, and, bleg, twenty, quux, one, foo, bar], NC).
%@ T = op(*, op(+, 20, 1), 100),
%@ NC = [and, bleg, twenty, quux, one, foo, bar].
%% ?- parse_number(T, [two, hundred, thousand], _).
%@ T = op(*, op(*, 2, 100), 1000).
%% ?- parse_number(T, [twenty, one, hundred, thousand], _).
%@ T = op(*, op(*, op(+, 20, 1), 100), 1000).
%% ?- parse_number(T, [thirty, five, million, five, hundred, thirty, four], _).
%@ T = op(+, op(+, op(*, op(+, op(*, op(+, 30, 5), 1000000), 5), 100), 30), 4).
%% ?- parse_number(T, [foo, five, million], NC).
%@ false.
%% nlp_parse_power(?List, ?List) is det
%
% Parse powers
%
%% Order matters
parse_power(op(^, TB, 2)) -->
parse_polynomial_variable(TB),
[squared].
parse_power(op(^, TB, 3)) -->
parse_polynomial_variable(TB),
[cubed].
parse_power(op(^, TB, TN)) -->
parse_polynomial_variable(TB),
[raised, to],
parse_number(TN).
parse_power(TB) -->
parse_polynomial_variable(TB).
parse_operation(-) --> [minus].
parse_operation(+) --> [plus].
parse_operation(*) --> [times].
parse_polynomial_operand(T) --> parse_number(T).
parse_polynomial_operand(T) --> parse_power(T).
parse_polynomial_operand(load(T)) --> parse_stored_variable(T), { ! }.
:- dynamic polynomial_store/2.
parse_stored_variable(P) -->
[P],
{
atom_codes(P, L),
cons(F, R, L),
code_type(F, prolog_var_start),
maplist(code_type_swap(prolog_identifier_continue), R)
}.
%% Tests:
%% ?- parse_stored_variable(P, ['P1'], _).
%@ P = 'P1'.
%% ?- parse_stored_variable(P, ['x1'], _).
%@ false.
code_type_swap(X, Y) :- code_type(Y, X).
parse_polynomial_variable(B) -->
[B],
{ polynomial_variable(B) }.
parse_polynomial(T) -->
[polynomial],
{ ! },
parse_polynomial_explicit(_-_, T).
parse_polynomial(T, NC, NC) :-
not(parse_polynomial_explicit(_-_, T, NC, _)),
!.
parse_polynomial(T) -->
parse_polynomial_explicit(_-_, T),
!.
%% Tests:
%% ?- parse_polynomial(T, [], _).
%@ false.
%% ?- parse_polynomial(T, [two], _).
%@ T = 2.
%% ?- parse_polynomial(T, [two, times, three], _).
%@ T = op(*, 2, 3).
%% ?- parse_polynomial(T, [two, times, three, plus, four], _).
%@ T = op(+, op(*, 2, 3), 4).
%% ?- parse_polynomial(T, [two, plus, three, times, four], _).
%@ T = op(+, 2, op(*, 3, 4)).
%% ?- parse_polynomial(T, [two, plus, three, times, four, plus, six, times, five], _).
%@ T = op(+, 2, op(+, op(*, 3, 4), op(*, 6, 5))).
%% ?- parse_polynomial(T, [two, times, times, two], NC), write(T).
%@ _2986 %% NOTE Potential problem. It seems NC isn't unified with the list, if it fails
%@ NC = [two, times, times, two].
%% ?- parse_polynomial(T, [two, plus, x, times, four], _).
%@ T = op(+, 2, op(*, x, 4)).
%% ?- parse_polynomial(T, [two, plus, x, times, four, plus, y, raised, to, five], _).
%@ T = op(+, 2, op(+, op(*, x, 4), op(^, y, 5))).
%% ?- parse_polynomial(T, [two, plus, two, plus, one, times, y], _).
%@ true.
%@ T = op(+, op(+, 2, 2), op(*, 1, y)).
%% ?- parse_polynomial(T, [polynomial, 2, plus, 3, plus, 4, y], NC).
%@ T = op(+, op(+, 2, 3), op(*, 4, y)),
%@ NC = [].
parse_polynomial_explicit(void-_, T) -->
parse_polynomial_operand(TL),
parse_operation(Op),
!,
parse_polynomial_explicit(op(Op, TL, TRP)-TRP, T).
parse_polynomial_explicit(TLP-TL, T) -->
parse_polynomial_operand(TL),
parse_operation(-),
!,
parse_polynomial_explicit(op(-, TLP, TRP)-TRP, T).
parse_polynomial_explicit(TLP-TL, T) -->
parse_polynomial_operand(TL),
parse_operation(+),
!,
parse_polynomial_explicit(op(+, TLP, TRP)-TRP, T).
parse_polynomial_explicit(TLP-T, TLP) -->
parse_polynomial_operand(TL),
parse_operation(*),
!,
parse_polynomial_explicit(op(*, TL, TRP)-TRP, T).
parse_polynomial_explicit(TLP-T, TLP) -->
parse_polynomial_operand(TL),
parse_polynomial_explicit(op(*, TL, TRP)-TRP, T),
!.
parse_polynomial_explicit(TLP-TL, TLP) -->
{ TLP \= void },
parse_polynomial_operand(TL),
!,
{ TL \= void }.
parse_polynomial_explicit(void-_, T) -->
parse_polynomial_operand(T),
!,
{ T \= void }.
parse_command(help_menu) -->
[help].
parse_command(help(C)) -->
[tell],
[me],
[about],
[C].
parse_command(show_stored_polynomials) -->
[show, stored, polynomials].
parse_command(forget(P)) -->
[forget],
parse_stored_variable(P).
parse_command(show(store(P), T)) -->
[show],
parse_polynomial(T),
[as],
parse_stored_variable(P).
parse_command(show(P, void)) -->
[show],
parse_stored_variable(P).
parse_command(show(void, T)) -->
[show],
parse_polynomial(T),
{ nonvar(T) }.
parse_command(store(P, T)) -->
[let],
parse_stored_variable(P),
[be],
parse_polynomial(T).
parse_command(store(P, T)) -->
[store],
parse_polynomial(T),
[as],
parse_stored_variable(P).
parse_command(simplify(T)) -->
[simplify],
parse_polynomial(T).
parse_command(multiply(TN, TP)) -->
[multiply],
parse_polynomial(TN),
[by],
parse_polynomial(TP).
parse_command(op(-, TN, TP)) -->
[sub],
parse_polynomial(TN),
[X],
{ member(X, [to, with]) },
parse_polynomial(TP).
parse_command(op(+, TN, TP)) -->
[add],
parse_polynomial(TN),
[X],
{ member(X, [to, with]) },
parse_polynomial(TP).
%% Tests:
%% ?- parse_command(T, [show, 3], NC).
%@ T = show(void, 3),
%@ NC = [] .
%% ?- parse_command(T, [add, 3, plus, x, to, 4, plus, x], NC).
%@ T = op(+, op(+, 3, x), op(+, 4, x)),
%@ NC = [] ;
%@ false.
parse_input(command(TCL, TCR)) -->
parse_command(TCL),
[and],
!,
parse_input(TCR).
parse_input(command(TC, void)) -->
parse_command(TC).
%% ?- parse_input(CT, [show, 3], _).
%@ CT = command(show(void, 3), void).
/*******************************
* UI *
*******************************/
/*
poly2list/2 transforms a list representing a polynomial (second
argument) into a polynomial represented as an expression (first
argument) and vice-versa.
*/
poly2list(P, L) :-
is_polynomial_valid_in_predicate(P, "poly2list"),
polynomial_to_list(P, L),
!.
/*
simpolylist/2 simplifies a polynomial represented as a list into
another polynomial as a list.
*/
simpoly_list(L, S) :-
is_polynomial_as_list_valid_in_predicate(L, "simpoly_list"),
simplify_polynomial_as_list(L, S),
!.
/*
simpoly/2 simplifies a polynomial represented as an expression
as another polynomial as an expression.
*/
simpoly(P, S) :-
is_polynomial_valid_in_predicate(P, "simpoly"),
simplify_polynomial(P, S),
!.
%% Tests:
%% ?- simpoly(2+2+1*y, S).
%@ S = y+4.
/*
scalepoly/3 multiplies a polynomial represented as an expression by a scalar
resulting in a second polynomial. The two first arguments are assumed to
be ground. The polynomial resulting from the sum is in simplified form.
*/
scalepoly(P1, C, S) :-
is_polynomial_valid_in_predicate(P1, "scalepoly"),
is_number_valid_in_predicate(C, "scalepoly"),
scale_polynomial(P1, C, S),
!.
%% Tests:
%% ?- scalepoly(3*x*z+2*z, 4, S).
%@ S = 12*x*z+8*z.
%% ?- scalepoly(3*x*z+2*z, 2, S).
%@ S = 6*x*z+4*z.
/*
addpoly/3 adds two polynomials as expressions resulting in a
third one. The two first arguments are assumed to be ground.
The polynomial resulting from the sum is in simplified form.
*/
addpoly(P1, P2, S) :-
is_polynomial_valid_in_predicate(P1, "addpoly"),
is_polynomial_valid_in_predicate(P2, "addpoly"),
add_polynomial(P1, P2, S),
!.
%% Tests:
%% ?- addpoly(3 + x, 3 - x, S).
%@ S = 6.
%% is_polynomial_valid_in_predicate(+T, +F) is det
%
% Returns true if valid polynomial, fails with UI message otherwise.
% The failure message reports which polynomial is invalid and in which
% predicate the problem ocurred.
%
is_polynomial_valid_in_predicate(P, _) :-
%% If P is a valid polynomial, return true
polynomial(P),
!.
is_polynomial_valid_in_predicate(P, F) :-
%% Otherwise, write the polynomial and fails
write("Invalid polynomial in "),
write(F),
write(": "),
write(P),
fail.
%% Tests:
%% ?- is_polynomial_valid_in_predicate(1-x, "Test").
%@ true.
%% ?- is_polynomial_valid_in_predicate(a*4-0*x, "Test").
%@ Invalid polynomial in Test: a*4-0*x
%@ false.
%% is_polynomial_as_list_valid_in_predicate(+L, +F) is det
%
% Returns true if the polynomial represented as list is valid,
% fails with UI message otherwise.
% The failure message reports which polynomial is invalid and
% in which predicate the problem ocurred.
%
is_polynomial_as_list_valid_in_predicate(L, F) :-
%% If L is a valid polynomial, return true
list_to_polynomial(L, P),
is_polynomial_valid_in_predicate(P, F).
%% Tests:
%% ?- is_polynomial_as_list_valid_in_predicate([1], "Test").
%@ true.
%% ?- is_polynomial_as_list_valid_in_predicate([0*x, a*4], "Test").
%@ Invalid polynomial in Test: a*4+0*x
%@ false.
%% is_number_valid_in_predicate(+C:number, +F:string) is det
%
% Validates that C is a number or prints F and it then it
%
is_number_valid_in_predicate(C, _) :-
number(C),
!.
is_number_valid_in_predicate(C, F) :-
%% Writes the argument and fails
write("Invalid number in "),
write(F),
write(": "),
write(C),
fail.
/*******************************
* BACKEND *
*******************************/
%% polynomial_variable_list(-List) is det
%
% List of possible polynomial variables
%
polynomial_variable_list([x, y, z]).
%% polynomial_variable(?X:atom) is semidet
%
% Returns true if X is a polynomial variable, false otherwise.
%
polynomial_variable(X) :-
polynomial_variable_list(V),
member(X, V).
%% Tests:
%% ?- polynomial_variable(x).
%@ true .
%% ?- polynomial_variable(a).
%@ false.
%% power(+X:atom) is semidet
%
% Returns true if X is a power term, false otherwise.
%
power(P^N) :-
%% CLPFD comparison. Reversible
N #>= 1,
polynomial_variable(P).
power(X) :-
polynomial_variable(X).
%% Tests:
%% ?- power(x).
%@ true .
%% ?- power(a).
%@ false.
%% ?- power(x^1).
%@ true .
%% ?- power(x^3).
%@ true .
%% ?- power(x^(-3)).
%@ false.
%% ?- power(-x).
%@ false.
%% ?- power(X).
%@ X = x^_462546,
%@ _462546 in 1..sup ;
%@ X = y^_462546,
%@ _462546 in 1..sup ;
%@ X = z^_462546,
%@ _462546 in 1..sup ;
%@ X = x ;
%@ X = y ;
%@ X = z.
%% term(+N:atom) is semidet
%
% Returns true if N is a term, false otherwise.
%
term(N) :-
% If N is not a free variable
nonvar(N),
% Assert it as a number
number(N).
term(N) :-
% If N is a free variable and not compound
not(compound(N)),
var(N),
% Assert it must be between negative and positive infinity
% This uses the CLPR library, which makes this reversible,
% whereas `number(N)` is always false, since it only succeeds
% if the argument is bound (to a integer or float)
{N >= 0; N < 0}.
term(X) :-
power(X).
term(-X) :-
power(X).
term(L * In) :-
term(L),
term(In).
%% Tests:
%% ?- term(2*x^3).
%@ true .
%% ?- term(x^(-3)).
%@ false.
%% ?- term(a).
%@ false.
%% ?- term(-1*x).
%@ true .
%% ?- term(-x).
%@ true .
%% ?- term((-3)*x^2).
%@ true .
%% ?- term(3.2*x).
%@ true .
%% ?- term(-x*(-z)).
%@ true .
%% ?- term(X).
%@ {X>=0.0} ;
%@ {X<0.0} ;
%@ X = x^_111514,
%@ _111514 in 1..sup ;
%@ X = y^_111514,
%@ _111514 in 1..sup ;
%@ X = z^_111514,
%@ _111514 in 1..sup ;
%@ X = x ;
%@ X = y ;
%@ X = z ;
%@ X = -x^_111522,
%@ _111522 in 1..sup ;
%@ X = -y^_111522,
%@ _111522 in 1..sup ;
%@ X = -z^_111522,
%@ _111522 in 1..sup ;
%@ X = -x ;
%@ X = -y ;
%@ X = -z ;
%% polynomial(+M:atom) is semidet
%
% Returns true if polynomial, false otherwise.
%
polynomial(M) :-
%% A polynomial is either a term
term(M).
polynomial(L + In) :-
%% Or a sum of terms
polynomial(L),
term(In).
polynomial(L - In) :-
%% Or a subtraction of terms
polynomial(L),
term(In).
%% Tests:
%% ?- polynomial(x).
%@ true .
%% ?- polynomial(x^3).
%@ true .
%% ?- polynomial(3*x^7).
%@ true .
%% ?- polynomial(2+3*x+4*x*y^3).
%@ true .
%% ?- polynomial(2 - 3*x + 4*x*y^3).
%@ true .
%% ?- polynomial(a).
%@ false.
%% ?- polynomial(x^(-3)).
%@ false.
%% ?- polynomial(-x + 3).
%@ true .
%% ?- polynomial(-x - -z).
%@ true .
%% power_to_canon(+T:atom, -T^N:atom) is semidet
%
% Returns a canon power term.
%
power_to_canon(T^N, T^N) :-
polynomial_variable(T),
% CLP(FD) operator to ensure N is different from 1,
% in a reversible way
N #\= 1.
power_to_canon(T, T^1) :-
polynomial_variable(T).
%% Tests:
%% ?- power_to_canon(x, X).
%@ X = x^1 .
%% ?- power_to_canon(-x, X).
%@ false.
%@ X = -1*x^1 .
%% ?- power_to_canon(X, x^1).
%@ X = x .
%% ?- power_to_canon(X, x^4).
%@ X = x^4 .
%% ?- power_to_canon(X, a^1).
%@ false.
%% ?- power_to_canon(X, x^(-3)).
%@ X = x^ -3 .
%% ?- power_to_canon(X, -1*x^1).
%@ X = -x .
%% term_to_list(?T, ?List) is semidet
%
% Converts a term to a list of its monomials and vice versa.
% Can verify if term and monomials list are compatible.
%
term_to_list(L * N, [N | TS]) :-
number(N),
term_to_list(L, TS).
term_to_list(L * P, [P2 | TS]) :-
power(P),
power_to_canon(P, P2),
term_to_list(L, TS).
term_to_list(L * -P, [-P2 | TS]) :-
power(P),
power_to_canon(P, P2),
term_to_list(L, TS).
term_to_list(N, [N]) :-
number(N).
term_to_list(P, [P2]) :-
power(P),
power_to_canon(P, P2).
term_to_list(-P, [-P2]) :-
power(P),
power_to_canon(P, P2).
%% Tests:
%% ?- term_to_list(1, X).
%@ X = [1] .
%% ?- term_to_list(-1, X).
%@ X = [-1] .
%% ?- term_to_list(x, X).
%@ X = [x^1] .
%% ?- term_to_list(-x, X).
%@ X = [-x^1] .
%% ?- term_to_list(2 * 3, X).
%@ X = [3, 2] .
%% ?- term_to_list(1*2*y*z*23*x*y*x^3*x, X).
%@ X = [x^1, x^3, y^1, x^1, 23, z^1, y^1, 2, 1] .
%% ?- term_to_list(1*2*y*z*23*x*y*(-1), X).
%@ X = [-1, y^1, x^1, 23, z^1, y^1, 2, 1] .
%% ?- term_to_list(X, [-1]).
%@ X = -1 .
%% ?- term_to_list(X, [x^1, -1]).
%@ X = -1*x .
%% ?- term_to_list(X, [-x^1]).
%@ X = -x .
%% ?- term_to_list(X, [y^1, x^1]).
%@ X = x*y .
%% ?- term_to_list(X, [x^4]).
%@ X = x^4 .
%% ?- term_to_list(X, [y^6, z^2, x^4]).
%@ X = x^4*z^2*y^6 .
%% ?- term_to_list(X, [y^6, z^2, x^4, -2]).
%@ X = -2*x^4*z^2*y^6 .
%% ?- term_to_list(X, [x^1, 0]).
%@ X = 0*x .
%% ?- term_to_list(X, [y^1, -2]).
%@ X = -2*y .
%% simplify_term(+Term_In:term, ?Term_Out:term) is det
%
% Simplifies a given term.
% This function can also be be used to verify if
% a term is simplified.
%
simplify_term(Term_In, Term_Out) :-
term_to_list(Term_In, L),
%% Sort the list of numbers and power to group them,
%% simplifying the job of `join_similar_parts_of_term`
sort(0, @=<, L, L2),
(
%% If there's a 0 in the list, then the whole term is 0
member(0, L2),
Term_Out = 0
;
%% Otherwise
(
%% If there's only one element, then the term was already simplified
%% This is done so that the `exclude` following doesn't remove all ones
length(L2, 1),
Term_Out = Term_In
;
%% Remove all remaining ones
exclude(==(1), L2, L3),
join_similar_parts_of_term(L3, L4),
%% Reverse the list, since the following call gives the result in the
%% reverse order otherwise
reverse(L4, L5),
term_to_list(Term_Out, L5)
)
),
% First result is always the most simplified form.
!.
%% Tests:
%% ?- simplify_term(1, X).
%@ X = 1.
%% ?- simplify_term(x, X).
%@ X = x.
%% ?- simplify_term(2*y*z*x^3*x, X).
%@ X = 2*x^4*y*z.
%% ?- simplify_term(1*y*z*x^3*x, X).
%@ X = x^4*y*z.
%% ?- simplify_term(0*y*z*x^3*x, X).
%@ X = 0.
%% ?- simplify_term(6*y*z*7*x*y*x^3*x, X).
%@ X = 42*x^5*y^2*z.
%% ?- simplify_term(-x, X).
%@ X = -x.
%% ?- simplify_term(-x*y*(-z)*3, X).
%@ X = 3* -x* -z*y.
%% ?- simplify_term(a, X).
%@ false.
%% ?- simplify_term(x^(-3), X).
%@ false.
%% join_similar_parts_of_term(+List, -List) is det
%
% Combine powers of the same variable in the given list.
% Requires that the list be sorted.
%
join_similar_parts_of_term([P1, P2 | L], L2) :-
%% If both symbols are powers
power(P1),
power(P2),
%% Decompose them into their parts
B^N1 = P1,
B^N2 = P2,
%% Sum the exponent
N is N1 + N2,
join_similar_parts_of_term([B^N | L], L2),
% First result is always the most simplified form.
!.
join_similar_parts_of_term([N1, N2 | L], L2) :-
%% If they are both numbers
number(N1),
number(N2),
%% Multiply them
N is N1 * N2,
join_similar_parts_of_term([N | L], L2),
% First result is always the most simplified form.
!.
join_similar_parts_of_term([X | L], [X | L2]) :-
%% Otherwise consume one element and recurse
join_similar_parts_of_term(L, L2),
% First result is always the most simplified form.
!.
join_similar_parts_of_term([], []).
%% Tests:
%% ?- join_similar_parts_of_term([3], T).
%@ T = [3].
%% ?- join_similar_parts_of_term([x^2], T).
%@ T = [x^2].
%% ?- join_similar_parts_of_term([x^1, x^1, x^1, x^1], T).
%@ T = [x^4].
%% ?- join_similar_parts_of_term([2, 3, x^1, x^2], T).
%@ T = [6, x^3].
%% ?- join_similar_parts_of_term([2, 3, x^1, x^2, y^1, y^6], T).
%@ T = [6, x^3, y^7].
%% ?- join_similar_parts_of_term([2, 3, -x^1, -x^2], T).
%@ T = [6, -x^1, -x^2].
%% simplify_polynomial(+P:atom, -P2:atom) is det
%
% Simplifies a polynomial.
%
simplify_polynomial(0, 0) :-
% 0 is already fully simplified. This is an
% exception to the following algorithm
!.
simplify_polynomial(P, P2) :-
polynomial_to_list(P, L),
simplify_polynomial_as_list(L, L2),
list_to_polynomial(L2, P2),
%% The first result is the most simplified one
!.
%% Tests:
%% ?- simplify_polynomial(1, X).
%@ X = 1.
%% ?- simplify_polynomial(0, X).
%@ X = 0.
%% ?- simplify_polynomial(x, X).
%@ X = x.
%% ?- simplify_polynomial(x*x, X).
%@ X = x^2.
%% ?- simplify_polynomial(2 + 2, X).
%@ X = 2*2.
%% ?- simplify_polynomial(x + x, X).
%@ X = 2*x.
%% ?- simplify_polynomial(0 + x*x, X).
%@ X = x^2.
%% ?- simplify_polynomial(x^2*x + 3*x^3, X).
%@ X = 4*x^3.
%% ?- simplify_polynomial(x^2*x + 3*x^3 + x^3 + x*x*x, X).
%@ X = 6*x^3.
%% ?- simplify_polynomial(x^2*x + 3*x^3 + x^3 + x*x*4 + z, X).
%@ X = 5*x^3+4*x^2+z.
%% ?- simplify_polynomial(x^2*x + 3*x^3 - x^3 - x*x*4 + z, X).
%@ X = 3*x^3-4*x^2+z.
%% ?- simplify_polynomial(x + 1 + x, X).
%@ X = 2*x+1.
%% ?- simplify_polynomial(x + 1 + x + 1 + x + 1 + x, X).
%@ X = 4*x+3.
%% simplify_polynomial_as_list(+L1:List,-L3:List) is det
%
% Simplifies a polynomial represented as a list.
%
simplify_polynomial_as_list(L, L14) :-
%% Convert each term to a list
maplist(term_to_list, L, L2),
%% Sort each sublist so that the next
%% sort gives the correct results
maplist(sort(0, @>=), L2, L3),
%% Sort the outer list
sort(0, @>=, L3, L4),
%% For each of the parts of the terms, join them
maplist(join_similar_parts_of_term, L4, L5),
%% Sort each of the sublists
%% Done so the next call simplifies has less work
maplist(sort(0, @=<), L5, L6),
join_similar_terms(L6, L7),
%% Exclude any sublist that includes a 0 (such as the
%% equivalent to the term 0*x)
exclude(member(0), L7, L8),
%% Reverse each sublist, because the next call
%% reverses the result
maplist(reverse, L8, L9),
maplist(term_to_list, L10, L9),
%% Delete any 0 from the list
delete(L10, 0, L11),
%% Sort list converting back gives the result in the correct order
sort(0, @=<, L11, L12),
(
%% If the list is empty, the result is a list with 0
L12 = [], L13 = [0]
;
%% Otherwise, this is the result
L13 = L12
),
%% Further make sure all terms are simplified
maplist(simplify_term, L13, L14).
%% Tests:
%% ?- simplify_polynomial_as_list([x, 1, x^2, x*y, 3*x^2, 4*x], L).
%@ L = [1, 4*x^2, 5*x, x*y] .
%% ?- simplify_polynomial_as_list([1, x^2, x*y, 3*x^2, -4, -1*x], L).
%@ L = [-3, -1*x, 4*x^2, x*y] .
%% ?- simplify_polynomial_as_list([1, 1*x], L).
%@ L = [1, x] .
%% ?- simplify_polynomial_as_list([0*x, 0], L).
%@ L = [0] .
%% join_similar_terms(+P:List, -P2:List) is det
%
% Joins similar sublists representing terms by using
% `add_terms` to check if they can be merged and perform
% the addition. Requires the list of list be sorted with
% `maplist(sort(0, @>=), L, L2),
% sort(0, @>=, L2, L3)`
% and that the sublists to be sorted with
% `sort(0, @=<)` since that is inherited from `add_terms`.
%
join_similar_terms([TL, TR | L], L2) :-
%% Check if terms can be added and add them
add_terms(TL, TR, T2),
%% Recurse, accumulation on the first element
join_similar_terms([T2 | L], L2),
%% Give only first result. Red cut
!.
join_similar_terms([X | L], [X | L2]) :-
%% If a pair of elements can't be added, skip one
%% and recurse
join_similar_terms(L, L2),
%% Give only first result. Red cut
!.
join_similar_terms([], []).
%% Tests:
%% ?- join_similar_terms([[2, x^3], [3, x^3], [x^3]], L).
%@ L = [[6, x^3]].
%% term_to_canon(+T:List, -T2:List) is det
%
% Adds the coefficient of the term as the first element of the list
%
%% Special cases to make this predicate reversible
term_to_canon([1], [1]) :-
!.
term_to_canon(L2, [1 | L]) :-
nonvar(L),
L2 = L,
!.
term_to_canon([-1], [-1]) :-
!.
term_to_canon([-P | L2], [-1, P | L]) :-
nonvar(L),
L2 = L,
!.
term_to_canon([N2 | L], [N | L]) :-
number(N),
N2 = N,
!.
%% Normal case
term_to_canon(L, [N | L2]) :-
term_to_canon_with_coefficient(N, L, L2),
!.
%% Tests:
%% ?- term_to_canon([2], T).
%@ T = [2].
%% ?- term_to_canon([-x], T).
%@ T = [-1, x].
%% ?- term_to_canon([-x^3], T).
%@ T = [-1, x^3].
%% ?- term_to_canon([x^1], T).
%@ T = [1, x^1].
%% ?- term_to_canon([x^3], T).
%@ T = [1, x^3].
%% ?- term_to_canon([x^3, z], T).
%@ T = [1, x^3, z].
%% ?- term_to_canon([2, x^3], T).
%@ T = [2, x^3].
%% ?- term_to_canon([2, -x^3], T).
%@ T = [-2, x^3].
%% ?- term_to_canon([2, -x^3, -z], T).
%@ T = [2, x^3, z].
%% ?- term_to_canon(L, [-1]).
%@ L = [-1].
%% ?- term_to_canon(L, [1]).
%@ L = [1].
%% ?- term_to_canon(L, [-2]).
%@ L = [-2].
%% ?- term_to_canon(L, [-2, x]).
%@ L = [-2, x].
%% ?- term_to_canon(L, [1, x]).
%@ L = [x].
%% ?- term_to_canon(L, [-1, x]).
%@ L = [-x].
%% ?- term_to_canon(L, [1, x, z, y]).
%@ L = [x, z, y].
%% ?- term_to_canon(L, [-1, x, z, y]).
%@ L = [-x, z, y].
%% term_to_canon_with_coefficient(-N:number, +L:List, -L2:List) is semidet
%
% Calculates the coefficient of the term and removes negations of powers,
% accumulating the results in N
%
term_to_canon_with_coefficient(N, [N2 | TS], TS2) :-
number(N2),
term_to_canon_with_coefficient(N3, TS, TS2),
N is N2 * N3,
!.
term_to_canon_with_coefficient(N, [P | TS], [P2 | TS2]) :-
sign_of_power(P, N2 * P2),
term_to_canon_with_coefficient(N3, TS, TS2),
N is N2 * N3,
!.
term_to_canon_with_coefficient(N, [], []) :-
nonvar(N);
N = 1.
%% Tests:
%% ?- term_to_canon_with_coefficient(N, [x], L).
%@ N = 1,
%@ L = [x].
%% ?- term_to_canon_with_coefficient(N, [x, x^2, 2], L).
%@ N = 2,
%@ L = [x^1, x^2].
%% ?- term_to_canon_with_coefficient(N, [x, x^2, 2, 4, z], L).
%@ N = 8,
%@ L = [x, x^2, z].
%% ?- term_to_canon_with_coefficient(N, [x, x^2, 2, 4, -z], L).
%@ N = -8,
%@ L = [x, x^2, z].
%% ?- term_to_canon_with_coefficient(N, [x, -x^2, 2, 4, -z], L).
%@ N = 8,
%@ L = [x, x^2, z].
%% ?- term_to_canon_with_coefficient(N, L, [x]).
%@ N = 1,
%@ L = [x].
%% ?- term_to_canon_with_coefficient(N, L, [1]).
%@ N = 1,
%@ L = [1].
%% ?- term_to_canon_with_coefficient(N, L, [2]).
%@ N = 1,
%@ L = [2].
%% sign_of_power(P:power, P:term) is det
%
% If there isn't a leading minus, multiplies the power by 1,
% otherwise by a -1. This way it prefers the positive version.
% Not idempotent
%
sign_of_power(P, 1*P) :-
%% If P can't unify with a minus followed by an unnamed variable
P \= -_,
!.
sign_of_power(-P, -1*P).
%% Tests:
%% ?- sign_of_power(x, X).
%@ X = 1*x.
%% ?- sign_of_power(-x, X).
%@ X = -1*x.
%% ?- sign_of_power(X, 1*x).
%@ X = x.
%% ?- sign_of_power(X, -1*x).
%@ X = -x.
%% add_terms(+L:List, +In:List, -Result:List) is det
%
% Adds two terms represented as list by adding
% the coeficients if the power is the same.
% Returns false if they can't be added
% Requires the list of terms to be simplified.
%
add_terms([NL | TL], [NR | TR], [N2 | TL2]) :-
%% Convert each term to a canon form. This ensures they
%% have a number in front, so it can be added
term_to_canon([NL | TL], [NL2 | TL2]),
term_to_canon([NR | TR], [NR2 | TR2]),
%% If the rest of the term is the same
TL2 == TR2,
%% Add the coeficients
N2 is NL2 + NR2.
%% Tests
%% ?- add_terms([1], [1], In).
%@ In = [2].
%% ?- add_terms([x], [x], In).
%@ In = [2, x].
%% ?- add_terms([2, x^3], [x^3], In).
%@ In = [3, x^3].
%% ?- add_terms([2, x^3], [3, x^3], In).
%@ In = [5, x^3].
%% ?- add_terms([2, x^3], [3, x^2], In).
%@ false.
%% polynomial_to_list(+P:polynomial, -L:List) is det
%
% Converts a polynomial in a list.
%
polynomial_to_list(L - T, [T2 | LS]) :-
term(T),
negate_term(T, T2),
polynomial_to_list(L, LS),
!.
polynomial_to_list(L + T, [T | LS]) :-
term(T),
polynomial_to_list(L, LS),
!.
polynomial_to_list(T, [T]) :-
term(T),
!.
%% Tests:
%% ?- polynomial_to_list(2, S).
%@ S = [2].
%% ?- polynomial_to_list(x^2, S).
%@ S = [x^2].
%% ?- polynomial_to_list(x^2 + x^2, S).
%@ S = [x^2, x^2].
%% ?- polynomial_to_list(2*x^2+5+y*2, S).
%@ S = [y*2, 5, 2*x^2].
%% ?- polynomial_to_list(2*x^2+5-y*2, S).
%@ S = [-2*y, 5, 2*x^2].
%% ?- polynomial_to_list(2*x^2-5-y*2, S).
%@ S = [-2*y, -5, 2*x^2].
%% list_to_polynomial(+L:List, -P:Polynomial) is det
%
% Converts a list in a polynomial.
% An empty list will return false.
%
list_to_polynomial([T1|T2], P) :-
% Start recursive calls until we are in the
% end of the list. We know that the `-` will
% always be at the left of a term.
list_to_polynomial(T2, L1),
(
% If this is a negative term
term_string(T1, S1),
string_chars(S1, [First|_]),
First = -,
% Concat them
term_string(L1, S2),
string_concat(S2,S1,S3),
term_string(P, S3)
;
% Otherwise sum them
P = L1+T1
),
% The others computations are semantically meaningless
!.
list_to_polynomial([T], T).
%% Tests:
%% ?- list_to_polynomial([1, x, x^2], P).
%@ P = x^2+x+1.
%% ?- list_to_polynomial([-1, -x, -x^2], P).
%@ P = -x^2-x-1.
%% ?- list_to_polynomial([1, -x, x^2], P).
%@ P = x^2-x+1.
%% ?- list_to_polynomial([x^2, x, 1], P).
%@ P = 1+x+x^2.
%% ?- list_to_polynomial([a,-e], P).
%@ P = -e+a.
%% ?- list_to_polynomial([], P).
%@ false.
%% ?- list_to_polynomial([a], P).
%@ P = a.
%% negate_term(T, T2) is det
%
% Negate the coeficient of a term and return the negated term.
%
negate_term(T, T2) :-
term_to_list(T, L),
%% Ensure there is a coeficient
term_to_canon(L, L2),
[N | In] = L2,
%% (-)/1 is an operator, needs to be evaluated, otherwise
%% it gives a symbolic result, which messes with further processing
N2 is -N,
%% Convert the term back from canonic form
term_to_canon(L3, [N2 | In]),
%% Reverse the order of the list, because converting
%% implicitly reverses it
reverse(L3, L4),
term_to_list(T2, L4),
!.
%% Tests:
%% ?- negate_term(1, In).
%@ In = -1.
%% ?- negate_term(x, In).
%@ In = -x.
%% ?- negate_term(-x, In).
%@ In = x.
%% ?- negate_term(x^2, In).
%@ In = -x^2.
%% ?- negate_term(3*x*y^2, In).
%@ In = -3*y^2*x.
%% scale_polynomial(+P:Polynomial,+C:Constant,-S:Polynomial) is det
%
% Multiplies a polynomial by a scalar.
%
scale_polynomial(P, C, S) :-
polynomial_to_list(P, L),
%% Convert each term to a list
maplist(term_to_list, L, L2),
%% Canonize terms
maplist(term_to_canon, L2, L3),
%% Append C to the start of each sublist
maplist(cons(C), L3, L4),
%% Convert to a list of terms
maplist(term_to_list, L5, L4),
%% Simplify the resulting polynomial
simplify_polynomial_as_list(L5, L6),
%% Return as a simplified polynomial
list_to_polynomial(L6, S),
!.
%% Tests:
%% ?- scale_polynomial(3*x^2, 2, S).
%@ S = 6*x^2.
%% cons(+C:atom, +L:List, -L2:List) is det
%
% Add an atom C to the head of a list L.
%
cons(C, L, [C | L]).
%% Tests:
%% ?- cons(C, L, L2).
%@ L2 = [C|L].
%% add_polynomial(+P1:polynomial,+P2:polynomial,-S:polynomial) is det
%
% S = P1 + P2.
%
add_polynomial(P1, P2, S) :-
%% Convert both polynomials to lists
polynomial_to_list(P1, L1),
polynomial_to_list(P2, L2),
%% Join them
append(L1, L2, L3),
%% Simplify the resulting polynomial
simplify_polynomial_as_list(L3, L4),
%% Convert back
list_to_polynomial(L4, S),
!.
%% Tests:
%% ?- add_polynomial(2, 2, S).
%@ S = 4.
%% ?- add_polynomial(x, x, S).
%@ S = 2*x.
%% ?- add_polynomial(2*x+5*z, 2*z+6*x, S).
%@ S = 8*x+7*z.