diff --git a/polimani.pl b/polimani.pl index f3c60e3..b686116 100644 --- a/polimani.pl +++ b/polimani.pl @@ -1,15 +1,81 @@ %% -*- mode: prolog-*- %% vim: set softtabstop=4 shiftwidth=4 tabstop=4 expandtab: -%% Follows 'Coding guidelines for Prolog' - Theory and Practice of Logic Programming -%% https://doi.org/10.1017/S1471068411000391 -%% Import the Constraint Logic Programming over Finite Domains lybrary -%% 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. +/** + * + * 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 lybrary + * 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)). + + /******************************* + * USER INTERFACE * + *******************************/ +/* + poly2list/2 transforms a list representing a polynomial (second + argument) into a polynomial represented as an expression (first argu- + ment) and vice-versa. +*/ +poly2list(P, L) :- + polynomial_to_list(P, L). + +/* + simpolylist/2 simplifies a polynomial represented as a list into + another polynomial as a list. +*/ +simpoly_list(L, S) :- + simplify_polynomial_list(L, S). + +/* + simpoly/2 simplifies a polynomial represented as an expression + as another polynomial as an expression. +*/ +simpoly(P, S) :- + simplify_polynomial(P, S). + +/* + 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, P2, S) :- + scale_polynomial(P1, P2, S). + +/* + 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) :- + add_polynomial(P1, P2, S). + + + /******************************* + * BACKEND * + *******************************/ + %% polynomial_variable_list(-List) is det % % List of possible polynomial variables @@ -84,6 +150,8 @@ term(L * R) :- %@ false. %% ?- term(a). %@ false. +%% ?- term(-1*x). +%@ true . %% ?- term((-3)*x^2). %@ true . %% ?- term(3.2*x). @@ -178,8 +246,17 @@ term_to_list(P, [P2]) :- %% Tests: %% ?- term_to_list(1, X). %@ X = [1] . +%% ?- term_to_list(-1, X). +%@ X = [-1] . %% ?- 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(X, [-1]). +%@ X = -1 . +%% ?- term_to_list(X, [x^1, -1]). +%@ X = -1*x . +%% ?- term_to_list(X, [- 1, x^1]). +%@ false. +%@ X = x* -1 . %% ?- term_to_list(X, [y^1, x^1]). %@ X = x*y . %% ?- term_to_list(X, [x^4]). @@ -203,7 +280,7 @@ simplify_term(Term_In, Term_Out) :- Term_Out = Term_In ); exclude(==(1), L2, L3), - join_like_terms(L3, L4), + join_similar_parts_of_term(L3, L4), sort(0, @>=, L4, L5), term_to_list(Term_Out, L5) ), @@ -227,112 +304,218 @@ simplify_term(Term_In, Term_Out) :- %% ?- simplify_term(x^(-3), X). %@ false. -%% join_like_terms(+List, -List) +%% join_similar_parts_of_term(+List, -List) % % Combine powers of the same variable in the given list % -join_like_terms([P1, P2 | L], [B^N | L2]) :- +join_similar_parts_of_term([P1, P2 | L], L2) :- power(P1), power(P2), B^N1 = P1, B^N2 = P2, N is N1 + N2, - join_like_terms(L, L2). -join_like_terms([N1, N2 | L], [N | L2]) :- + join_similar_parts_of_term([B^N | L], L2). +join_similar_parts_of_term([N1, N2 | L], L2) :- number(N1), number(N2), N is N1 * N2, - join_like_terms(L, L2). -join_like_terms([X | L], [X | L2]) :- - join_like_terms(L, L2). -join_like_terms([], []). + join_similar_parts_of_term([N | L], L2). +join_similar_parts_of_term([X | L], [X | L2]) :- + join_similar_parts_of_term(L, L2). +join_similar_parts_of_term([], []). %% Tests: -%% ?- join_like_terms([2, 3, x^1, x^2], T). +%% ?- 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_like_terms([2, 3, x^1, x^2, y^1, y^6], T). +%% ?- join_similar_parts_of_term([2, 3, x^1, x^2, y^1, y^6], T). %@ T = [6, x^3, y^7] . %% simplify_polynomial(+P:atom, -P2:atom) is det % % Simplifies a polynomial. -% TODO: not everything is a +, there are - % -simplify_polynomial(M, M2) :- - %% Are we dealing with a valid term? - %is_term_valid_in_predicate(M, "simplify_polynomial(M, M2)"), - %% term(M), - %% If so, simplify it. - simplify_term(M, M2), +simplify_polynomial(0, 0) :- !. -simplify_polynomial(P + 0, P) :- - %% Ensure valid term - %is_term_valid_in_predicate(P, "simplify_polynomial(P + 0, P)"), - term(P), +simplify_polynomial(P, P2) :- + polynomial_to_list(P, L), + maplist(term_to_list, L, L2), + maplist(sort(0, @>=), L2, L3), + sort(0, @>=, L3, L4), + maplist(join_similar_parts_of_term, L4, L5), + maplist(sort(0, @=<), L5, L6), + join_similar_terms(L6, L7), + maplist(reverse, L7, L8), + maplist(term_to_list, L9, L8), + delete(L9, 0, L10), + sort(0, @=<, L10, L11), + list_to_polynomial(L11, P2), !. -simplify_polynomial(0 + P, P) :- - %% Ensure valid term - %is_term_valid_in_predicate(P, "simplify_polynomial(0 + P, P)"), - term(P), - !. -simplify_polynomial(P + M, P2 + M2) :- - simplify_polynomial(P, P2), - simplify_term(M, M2). -simplify_polynomial(P + M, P2 + M3) :- - monomial_parts(M, _, XExp), - delete_monomial(P, XExp, M2, P2), - !, - add_monomial(M, M2, M3). -simplify_polynomial(P + M, P2 + M2) :- - simplify_polynomial(P, P2), - simplify_term(M, M2). %% Tests: %% ?- simplify_polynomial(1, X). -%@ false. -%@ false. -%@ Invalid term in simplify_polynomial(M, M2): 1 -%@ false. +%@ 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 + 1 + x, X). +%@ X = 2*x+1. +%% ?- simplify_polynomial(x + 1 + x + 1 + x + 1 + x, X). +%@ X = 4*x+3*1. - -%% simplify_polynomial_list(+L1,-L3) is det +%% join_similar_terms(+P:ListList, -P2:ListList) is det % -% Simplifies a list of polynomials +% 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` % -simplify_polynomial_list([L1], L3) :- - simplify_polynomial(L1, L2), - L3 = [L2]. -simplify_polynomial_list([L1|L2],L3) :- - simplify_polynomial(L1, P1), - simplify_polynomial_list(L2, P2), - L3 = [P1|P2], - % There is nothing further to compute at this point +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 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, @=<)` +% +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(L, L). +%% Tests: +%% ?- term_to_canon([2], T). +%@ T = [2]. +%% ?- 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]. + +%% add_terms(+L:List, +R:List, -Result:List) is det +% +% Adds two terms represented as list by adding +% the coeficients if the power is the same. +% Requires the list of terms to be simplified. +% +add_terms([NL | TL], [NR | TR], [N2 | TL2]) :- + term_to_canon([NL | TL], [NL2 | TL2]), + term_to_canon([NR | TR], [NR2 | TR2]), + TL2 == TR2, + N2 is NL2 + NR2. +%% Tests +%% ?- add_terms([1], [1], R). +%@ R = [2]. +%% ?- add_terms([x], [x], R). +%@ R = [2, x]. +%% ?- add_terms([2, x^3], [x^3], R). +%@ R = [3, x^3]. +%% ?- add_terms([2, x^3], [3, x^3], R). +%@ R = [5, x^3]. + +%% simplify_polynomial_list(+L:list, -S:list) is det +% +% Simplifies a polynomial represented as a list +% +simplify_polynomial_list(L, S) :- + polynomial_to_list(P1, L), + simplify_polynomial(P1, P2), + polynomial_to_list(P2, S). %% polynomial_to_list(+P:polynomial, -L:List) % % Converts a polynomial in a list. -% TODO: not everything is a +, there are - % -polynomial_to_list(T1 + T2, L) :- - polynomial_to_list(T1, L1), - L = [T2|L1], - % The others computations are semantically meaningless - !. -polynomial_to_list(P, L) :- - L = [P]. +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*x^2+5+y*2, S). -%@S = [y*2, 5, 2*x^2]. +%% ?- 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] . +%% ?- polynomial_to_list(P, [2]). +%@ P = 2 . +%% ?- polynomial_to_list(P, [x]). +%@ P = x . +%% ?- polynomial_to_list(P, [x^2, x, 2.3]). +%@ Action (h for help) ? abort +%@ % Execution Aborted +%@ P = -2.3+x+x^2 . %% list_to_polynomial(+P:polynomial, -L:List) % % Converts a list in a polynomial. -% TODO: not everything is a +, there are - % list_to_polynomial([T1|T2], P) :- list_to_polynomial(T2, L1), ( not(L1 = []), - P = L1+T1 + ( + term_string(T1, S1), + string_chars(S1, [First|_]), + First = -, + term_string(L1, S2), + string_concat(S2,S1,S3), + term_string(P, S3) + ; + P = L1+T1 + ) ; P = T1 ), @@ -343,6 +526,31 @@ list_to_polynomial(T, P) :- %% Tests: %% TODO +%% 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), + sort(0, @=<, L, L2), + term_to_canon(L2, L3), + [N | R] = L3, + %% (-)/1 is an operator, needs to be evaluated, otherwise + %% it gives a symbolic result, which messes with further processing + N2 is -N, + reverse([N2 | R], L4), + term_to_list(T2, L4), + !. +%% Tests: +%% ?- negate_term(1, R). +%@ R = -1. +%% ?- negate_term(x, R). +%@ R = -1*x. +%% ?- negate_term(x^2, R). +%@ R = -1*x^2. +%% ?- negate_term(3*x*y^2, R). +%@ R = -3*x*y^2. + %% append_two_atoms_with_star(+V1, +V2, -R) is det % % Returns R = V1 * V2 @@ -370,11 +578,9 @@ scale_polynomial(P, C, S) :- polynomial_to_list(P, L), maplist(append_two_atoms_with_star(C), L, L2), list_to_polynomial(L2, S). -%simplify_polynomial(S1, S). %% Tests: %% ?- scale_polynomial(3*x^2, 2, S). %@ S = 2*3*x^2. -%@ S = 2*(3*x^2). %% add_polynomial(+P1:polynomial,+P2:polynomial,-S:polynomial) is det % @@ -389,70 +595,3 @@ add_polynomial(P1, P2, S) :- simplify_polynomial(P, S). %% Tests: % - -%% monomial_parts(X, Y, Z) -% -% TODO Maybe remove -% Separate monomial into it's parts. Given K*X^N, gives K and N -% -monomial_parts(X, 1, X) :- - power(X), - !. -monomial_parts(X^N, 1, X^N) :- - power(X^N), - !. -monomial_parts(K * M, K, M) :- - number(K), - !. -monomial_parts(K, K, indep) :- - number(K), - !. - - -delete_monomial(M, X, M, 0) :- - term(M), - monomial_parts(M, _, X), - !. -delete_monomial(M + M2, X, M, M2) :- - term(M2), - term(M), - monomial_parts(M, _, X), - !. -delete_monomial(P + M, X, M, P) :- - term(M), - monomial_parts(M, _, X), - !. -delete_monomial(P + M2, X, M, P2 + M2) :- - delete_monomial(P, X, M, P2). - -add_monomial(K1, K2, K3) :- - number(K1), - number(K2), !, - K3 is K1 + K2. -add_monomial(M1, M2, M3) :- - monomial_parts(M1, K1, XExp), - monomial_parts(M2, K2, XExp), - K3 is K1 + K2, - p_aux_add_monomial(K3, XExp, M3). - -p_aux_add_monomial(K, indep, K) :- - !. -p_aux_add_monomial(0, _, 0) :- - !. -p_aux_add_monomial(1, XExp, XExp) :- - !. -p_aux_add_monomial(K, XExp, K * XExp). - -closure_simplify_polynomial(P, P) :- - simplify_polynomial(P, P2), - P==P2, - !. -closure_simplify_polynomial(P, P3) :- - simplify_polynomial(P, P2), - closure_simplify_polynomial(P2, P3), - !. - -list_to_term([N | NS], N * L) :- - number(N), - term_to_list(L, NS). -