diff --git a/polymani.pl b/polymani.pl index ceb70a1..faa596c 100644 --- a/polymani.pl +++ b/polymani.pl @@ -27,6 +27,11 @@ * 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)). /******************************* @@ -82,6 +87,51 @@ addpoly(P1, P2, S) :- is_polynomial_valid_in_predicate(P2, "addpoly"), add_polynomial(P1, P2, S), !. +%% Tests: +%% ?- addpoly(3 + x, 3 - x, S). +%@ S = 0*x+6. TODO HERE + +%% 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) :- + %% Writes the polynomial and fails otherwise + write("Invalid polynomial in "), + write(F), + write(": "), + write(P), + fail. +%% Tests: +%% ?- is_polynomial_valid_in_predicate(1, "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. /******************************* @@ -112,12 +162,8 @@ polynomial_variable(X) :- % Returns true if X is a power term, false otherwise. % power(P^N) :- - ( - N #>= 1, - polynomial_variable(P) - ; - fail - ). + N #>= 1, + polynomial_variable(P). power(X) :- polynomial_variable(X). %% Tests: @@ -131,13 +177,15 @@ power(X) :- %@ true . %% ?- power(x^(-3)). %@ false. +%% ?- power(-x). +%@ false. %% ?- power(X). -%@ X = x^_2420, -%@ _2420 in 0..sup ; -%@ X = y^_2420, -%@ _2420 in 0..sup ; -%@ X = z^_2420, -%@ _2420 in 0..sup ; +%@ 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. @@ -148,22 +196,25 @@ power(X) :- % term(N) :- ( - % If N is non a free variable + % If N is not a free variable nonvar(N), % Assert it as a number number(N) ; % If N is a free variable - not(compound(N)), + %% not(compound(N)), var(N), % Assert it must be between negative and positive infinity % This uses the CLP(FD) library, which makes this reversible, % whereas `number(N)` is always false, since it only succeeds % if the argument is bound to a intger or float - N in inf..sup + %% N in inf..sup + {N >= 0; N < 0} ). term(X) :- power(X). +term(-X) :- + power(X). term(L * R) :- term(L), term(R). @@ -176,78 +227,35 @@ term(L * R) :- %@ 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 in inf..sup ; -%@ X = x^_1242, -%@ _1242 in 1..sup ; -%@ X = y^_1242, -%@ _1242 in 1..sup ; -%@ X = z^_1242, -%@ _1242 in 1..sup ; +%@ {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 = _1330*_1332, -%@ _1330 in inf..sup, -%@ _1332 in inf..sup ; -%@ X = _1406*x^_1414, -%@ _1406 in inf..sup, -%@ _1414 in 1..sup ; -%@ X = _1406*y^_1414, -%@ _1406 in inf..sup, -%@ _1414 in 1..sup ; -%@ X = _1406*z^_1414, -%@ _1406 in inf..sup, -%@ _1414 in 1..sup ; -%@ X = _1188*x, -%@ _1188 in inf..sup . -%% Doesn't give all possible terms, because number(N) is not reversible - -%% 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) :- - %% Writes the polynomial and fails otherwise - write("Invalid polynomial in "), - write(F), - write(": "), - write(P), - fail. -%% Tests: -%% ?- is_polynomial_valid_in_predicate(1, "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. +%@ 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 % @@ -279,6 +287,10 @@ polynomial(L - R) :- %@ false. %% ?- polynomial(x^(-3)). %@ false. +%% ?- polynomial(-x + 3). +%@ true . +%% ?- polynomial(-x - -z). +%@ true . %% power_to_canon(+T:atom, -T^N:atom) is semidet % @@ -291,9 +303,14 @@ power_to_canon(T^N, T^N) :- N #\= 1. power_to_canon(T, T^1) :- polynomial_variable(T). +%% power_to_canon(-P, -P2) :- +%% power_to_canon(P, P2). %% 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). @@ -302,6 +319,8 @@ power_to_canon(T, T^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 % @@ -317,16 +336,28 @@ 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] . +%@ 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). @@ -337,6 +368,9 @@ term_to_list(P, [P2]) :- %@ X = -1 . %% ?- term_to_list(X, [x^1, -1]). %@ X = -1*x . +%@ 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]). @@ -393,6 +427,10 @@ simplify_term(Term_In, Term_Out) :- %@ 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). @@ -439,6 +477,8 @@ join_similar_parts_of_term([], []). %@ 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 % @@ -511,8 +551,12 @@ simplify_polynomial_as_list(L, L11) :- %% 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] . +%@ 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] . +%@ L = [-3, -1*x, 4*x^2, x*y] . +%% ?- simplify_polynomial_as_list([0*x], L). +%@ L = [0*x] . %% join_similar_terms(+P:ListList, -P2:ListList) is det % @@ -544,34 +588,130 @@ join_similar_terms([], []). %% term_to_canon(+T:List, -T2:List) is det % -% Adds a 1 if there's no number in the list. -% Requires the list to be sorted such that the -% numbers come first. -% For instance with `sort(0, @=<)`. +% Adds the coefficient of the term as the first element of the list % -term_to_canon([T | TS], [1, T | TS]) :- - %% Since the list is sorted, if the first element - %% is not a number, then we need to add the 1 - not(number(T)), - %% Give only first result. Red cut +term_to_canon([1], [1]) :- !. -term_to_canon([T | TS], [N, T | TS]) :- - %% Since the list is sorted, if the first element - %% is not a number, then we need to add the 1 - not(number(T)), - N is -1, - %% Give only first result. Red cut +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, + !. +term_to_canon(L, [N | L2]) :- + %% N == 1 -> L = L2 + %% ; + term_to_canon_with_coefficient(N, L, L2), !. -term_to_canon(L, L). %% 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), + %% {N2 >= 0; N2 < 0}, + 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, +R:List, -Result:List) is det % @@ -678,28 +818,29 @@ list_to_polynomial([T], T). % negate_term(T, T2) :- term_to_list(T, L), - %% Sort the list, so the coeficient is the first element - sort(0, @=<, L, L2), %% Ensure there is a coeficient - term_to_canon(L2, L3), - [N | R] = L3, + term_to_canon(L, L2), + [N | R] = L2, %% (-)/1 is an operator, needs to be evaluated, otherwise %% it gives a symbolic result, which messes with further processing N2 is -N, %% Reverse the order of the list, because converting %% implicitly reverses it - reverse([N2 | R], L4), + term_to_canon(L3, [N2 | R]), + reverse(L3, L4), term_to_list(T2, L4), !. %% Tests: %% ?- negate_term(1, R). %@ R = -1. %% ?- negate_term(x, R). -%@ R = -1*x. +%@ R = -x. +%% ?- negate_term(-x, R). +%@ R = x. %% ?- negate_term(x^2, R). -%@ R = -1*x^2. +%@ R = -x^2. %% ?- negate_term(3*x*y^2, R). -%@ R = -3*x*y^2. +%@ R = -3*y^2*x. %% scale_polynomial(+P:Polynomial,+C:Constant,-S:Polynomial) is det %