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/polimani.pl

555 lines
12 KiB
Perl
Raw Normal View History

2018-11-17 23:53:49 +00:00
%% -*- mode: prolog-*-
2018-11-21 15:23:35 +00:00
%% vim: set softtabstop=4 shiftwidth=4 tabstop=4 expandtab:
2018-11-22 17:49:55 +00:00
/**
*
* 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.
*/
2018-11-22 11:51:19 +00:00
:- use_module(library(clpfd)).
2018-11-22 18:04:45 +00:00
/*******************************
* 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).
/*
2018-11-22 18:34:23 +00:00
simpoly/2 simplifies a polynomial represented as an expression
2018-11-22 18:04:45 +00:00
as another polynomial as an expression.
*/
simpoly(P, S) :-
simplify_polynomial(P, S).
/*
2018-11-22 18:34:23 +00:00
scalepoly/3 multiplies one polynomial as expression by a scalar
2018-11-22 18:04:45 +00:00
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).
/*
2018-11-22 18:34:23 +00:00
addpoly/3 adds two polynomials as expressions resulting in a
2018-11-22 18:04:45 +00:00
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
2018-11-18 16:33:09 +00:00
%
% List of possible polynomial variables
%
2018-11-19 16:59:53 +00:00
polynomial_variable_list([x, y, z]).
2018-11-17 16:14:13 +00:00
2018-11-18 16:33:09 +00:00
%% polynomial_variable(?X:atom) is det
%
% Returns true if X is a polynomial variable, false otherwise.
%
polynomial_variable(X) :-
2018-11-19 16:59:53 +00:00
polynomial_variable_list(V),
2018-11-19 15:56:48 +00:00
member(X, V).
2018-11-19 16:59:53 +00:00
%% Tests:
2018-11-20 16:14:53 +00:00
%% ?- polynomial_variable(x).
%@ true .
%% ?- polynomial_variable(a).
2018-11-22 11:51:19 +00:00
%@ false.
2018-11-17 16:14:13 +00:00
2018-11-22 11:51:19 +00:00
%% power(+X:atom) is semidet
2018-11-18 16:33:09 +00:00
%
2018-11-19 16:59:53 +00:00
% Returns true if X is a power term, false otherwise.
2018-11-18 16:33:09 +00:00
%
2018-11-22 12:34:42 +00:00
power(P^N) :-
(
2018-11-22 13:57:46 +00:00
zcompare((<), 0, N),
polynomial_variable(P)
;
fail
).
2018-11-18 16:33:09 +00:00
power(X) :-
2018-11-19 16:59:53 +00:00
polynomial_variable(X).
%% Tests:
2018-11-22 11:51:19 +00:00
%% ?- power(x).
%@ true .
2018-11-22 13:57:46 +00:00
%% ?- power(a).
%@ false.
2018-11-19 16:59:53 +00:00
%% ?- power(x^1).
2018-11-19 16:07:13 +00:00
%@ true .
2018-11-22 11:51:19 +00:00
%% ?- power(x^3).
%@ true .
2018-11-20 16:14:53 +00:00
%% ?- power(x^(-3)).
2018-11-22 13:57:46 +00:00
%@ false.
2018-11-22 11:51:19 +00:00
%% ?- power(X).
2018-11-22 13:57:46 +00:00
%@ X = x^_7334,
%@ _7334 in 1..sup ;
%@ X = y^_7334,
%@ _7334 in 1..sup ;
%@ X = z^_7334,
%@ _7334 in 1..sup ;
2018-11-22 11:51:19 +00:00
%@ X = x ;
%@ X = y ;
%@ X = z.
2018-11-18 16:33:09 +00:00
%% term(+N:atom) is det
%
2018-11-19 16:59:53 +00:00
% Returns true if N is a term, false otherwise.
2018-11-18 16:33:09 +00:00
%
term(N) :-
number(N).
2018-11-22 13:57:46 +00:00
%% N in inf..sup.
2018-11-18 16:33:09 +00:00
term(X) :-
power(X).
term(L * R) :-
term(L),
2018-11-20 16:14:53 +00:00
term(R).
2018-11-22 13:57:46 +00:00
%% append_two_atoms_with_star(L, R, T).
2018-11-19 16:59:53 +00:00
%% Tests:
2018-11-20 16:14:53 +00:00
%% ?- term(2*x^3).
%@ true .
%% ?- term(x^(-3)).
2018-11-22 11:51:19 +00:00
%@ false.
2018-11-22 13:57:46 +00:00
%% ?- term(a).
%@ false.
2018-11-22 11:51:19 +00:00
%% ?- term((-3)*x^2).
2018-11-20 16:14:53 +00:00
%@ true .
2018-11-22 13:57:46 +00:00
%% ?- term(3.2*x).
%@ true .
%% ?- term(X).
%% Doesn't give all possible terms, because number(N) is not reversible
%% The ic library seems to be able to help here, but it's not a part of
%% SwiPL by default
2018-11-19 16:59:53 +00:00
%% is_term_valid_in_predicate(+T, +F) is det
2018-11-18 16:33:09 +00:00
%
% Returns true if valid Term, fails with UI message otherwise.
% The fail message reports which Term is invalid and in which
2018-11-19 16:59:53 +00:00
% predicate the problem ocurred.
2018-11-18 16:33:09 +00:00
%
2018-11-19 16:59:53 +00:00
is_term_valid_in_predicate(T, F) :-
(
2018-11-18 16:33:09 +00:00
term(T)
;
2018-11-18 16:33:09 +00:00
write("Invalid term in "),
write(F),
write(": "),
write(T),
fail
).
2018-11-19 16:59:53 +00:00
%% Tests:
2018-11-22 13:57:46 +00:00
%% ?- is_term_valid_in_predicate(1, "Test").
2018-11-20 16:14:53 +00:00
%@ true .
2018-11-22 13:57:46 +00:00
%% ?- is_term_valid_in_predicate(a, "Test").
2018-11-18 16:33:09 +00:00
%% polynomial(+M:atom) is det
%
% Returns true if polynomial, false otherwise.
%
polynomial(M) :-
term(M).
polynomial(L + R) :-
polynomial(L),
2018-11-19 16:59:53 +00:00
term(R).
%% Tests:
2018-11-22 11:51:19 +00:00
%% ?- polynomial(x).
%@ true .
%% ?- polynomial(x^3).
%@ true .
%% ?- polynomial(3*x^7).
%@ true .
%% ?- polynomial(2 + 3*x + 4*x*y^3).
%@ true .
2018-11-22 13:57:46 +00:00
%% ?- polynomial(a).
%@ false.
%% ?- polynomial(x^(-3)).
%@ false.
2018-11-18 16:33:09 +00:00
%% power_to_canon(+T:atom, -T^N:atom) is det
%
% Returns a canon power term.
%
2018-11-19 16:59:53 +00:00
power_to_canon(T^N, T^N) :-
2018-11-22 11:51:19 +00:00
polynomial_variable(T),
2018-11-22 13:57:46 +00:00
N #\= 1.
2018-11-19 16:59:53 +00:00
power_to_canon(T, T^1) :-
polynomial_variable(T).
%% Tests:
%% ?- power_to_canon(x, X).
2018-11-22 11:51:19 +00:00
%@ X = x^1 .
%% ?- power_to_canon(X, x^1).
2018-11-19 16:59:53 +00:00
%@ X = x .
2018-11-22 11:51:19 +00:00
%% ?- power_to_canon(X, x^4).
%@ X = x^4 .
2018-11-22 13:57:46 +00:00
%% ?- power_to_canon(X, a^1).
%@ false.
%% ?- power_to_canon(X, x^(-3)).
%@ X = x^ -3 .
2018-11-19 16:59:53 +00:00
%% term_to_list(?T, ?List) is det
2018-11-18 16:33:09 +00:00
%
2018-11-19 16:59:53 +00:00
% Converts a term to a list and vice versa.
% Can verify if term and list are compatible.
2018-11-18 16:33:09 +00:00
%
term_to_list(L * N, [N | TS]) :-
number(N),
2018-11-19 16:59:53 +00:00
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).
%% Tests:
2018-11-22 13:57:46 +00:00
%% ?- term_to_list(1, X).
%@ X = [1] .
2018-11-20 16:14:53 +00:00
%% ?- 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] .
2018-11-19 16:59:53 +00:00
%% ?- term_to_list(X, [y^1, x^1]).
%@ X = x*y .
%% ?- term_to_list(X, [x^4]).
2018-11-22 11:51:19 +00:00
%@ X = x^4 .
2018-11-19 16:59:53 +00:00
%% ?- term_to_list(X, [y^6, z^2, x^4]).
%@ X = x^4*z^2*y^6 .
2018-11-20 16:14:53 +00:00
%% simplify_term(+Term_In:term, ?Term_Out:term) is det
2018-11-18 16:33:09 +00:00
%
2018-11-19 16:59:53 +00:00
% Simplifies a term.
2018-11-18 16:33:09 +00:00
%
2018-11-20 16:14:53 +00:00
simplify_term(Term_In, Term_Out) :-
term_to_list(Term_In, L),
2018-11-17 23:53:49 +00:00
sort(0, @=<, L, L2),
2018-11-20 16:14:53 +00:00
(
member(0, L2),
Term_Out = 0
;
2018-11-22 13:57:46 +00:00
(
length(L2, 1),
Term_Out = Term_In
);
2018-11-20 16:14:53 +00:00
exclude(==(1), L2, L3),
join_similar_parts_of_term(L3, L4),
2018-11-20 16:14:53 +00:00
sort(0, @>=, L4, L5),
term_to_list(Term_Out, L5)
),
% First result is always the most simplified form.
!.
2018-11-19 16:59:53 +00:00
%% Tests:
2018-11-22 13:57:46 +00:00
%% ?- simplify_term(1, X).
%@ X = 1.
%% ?- simplify_term(x, X).
%@ X = x.
%% ?- simplify_term(2*y*z*x^3*x, X).
2018-11-20 16:14:53 +00:00
%@ 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^2*x^3*y^2*z.
2018-11-22 13:57:46 +00:00
%% ?- simplify_term(a, X).
%@ false.
%% ?- simplify_term(x^(-3), X).
%@ false.
2018-11-17 23:53:49 +00:00
%% join_similar_parts_of_term(+List, -List)
2018-11-19 16:59:53 +00:00
%
% Combine powers of the same variable in the given list
%
join_similar_parts_of_term([P1, P2 | L], L2) :-
2018-11-19 16:59:53 +00:00
power(P1),
power(P2),
2018-11-19 15:56:48 +00:00
B^N1 = P1,
B^N2 = P2,
N is N1 + N2,
join_similar_parts_of_term([B^N | L], L2).
join_similar_parts_of_term([N1, N2 | L], L2) :-
2018-11-17 23:53:49 +00:00
number(N1),
number(N2),
N is N1 * N2,
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([], []).
2018-11-19 16:59:53 +00:00
%% 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).
2018-11-22 13:57:46 +00:00
%@ T = [6, x^3] .
%% ?- join_similar_parts_of_term([2, 3, x^1, x^2, y^1, y^6], T).
2018-11-22 13:57:46 +00:00
%@ T = [6, x^3, y^7] .
2018-11-19 16:59:53 +00:00
%% simplify_polynomial(+P:atom, -P2:atom) is det
2018-11-18 16:33:09 +00:00
%
2018-11-19 16:59:53 +00:00
% Simplifies a polynomial.
% TODO: not everything is a +, there are -
2018-11-18 16:33:09 +00:00
%
simplify_polynomial(0, 0) :-
2018-11-19 16:59:53 +00:00
!.
simplify_polynomial(P, P2) :-
polynomial_to_list(P, L),
maplist(term_to_list, L, L2),
maplist(join_similar_parts_of_term, L2, L3),
maplist(sort(0, @=<), L3, L4),
join_similar_terms(L4, L5),
transform_list(sort(0, @>=), L5, L6),
transform_list(term_to_list, L7, L6),
delete(L7, 0, L8),
polynomial_to_list(P2, L8),
2018-11-19 16:59:53 +00:00
!.
%% Tests:
2018-11-22 13:57:46 +00:00
%% ?- 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(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.
join_similar_terms([TL, TR | L], L2) :-
add_terms(TL, TR, T2),
join_similar_terms([T2 | L], L2),
%% Give only first result. Red cut
!.
join_similar_terms([X | L], [X | L2]) :-
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]].
2018-11-20 16:14:53 +00:00
term_to_canon([T], [1, T]) :-
%% Give only first result. Red cut
!.
term_to_canon(L, L).
%% Tests:
%% ?- term_to_canon([x^3], T).
%@ T = [1, x^3].
%% ?- term_to_canon([2, x^3], T).
%@ T = [2, x^3].
add_terms([NL | TL], [NR | TR], [N2 | TL2]) :-
term_to_canon([NL | TL], [NL2 | TL2]),
term_to_canon([NR | TR], [NR2 | TR2]),
TL2 == TR2,
number(NL2),
number(NR2),
N2 is NL2 + NR2.
%% Tests
%% ?- 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].
%% transform_list(+Pred, +L, -R) is det
%
% Apply predicate to each of the elements of L, producing R
%
transform_list(_, [], []).
transform_list(Pred, [L | LS], [R | RS]) :-
call(Pred, L, R),
transform_list(Pred, LS, RS),
!.
%% Tests:
%% ?- transform_list(term_to_list, [x, 2], L).
%@ L = [[x^1], [2]].
%% ?- transform_list(term_to_list, [x, x, 2], L).
%@ L = [[x^1], [x^1], [2]].
%% ?- transform_list(term_to_list, L, [[x^1], [x^1], [2]]).
%@ L = [x, x, 2].
%% simplify_polynomial_list(+L:list, -S:list) is det
2018-11-19 16:59:53 +00:00
%
% Simplifies a polynomial represented as a list
2018-11-19 16:59:53 +00:00
%
simplify_polynomial_list(L, S) :-
polynomial_to_list(P1, L),
simplify_polynomial(P1, P2),
polynomial_to_list(P2, S).
2018-11-17 16:14:13 +00:00
%% polynomial_to_list(+P:polynomial, -L:List)
%
% Converts a polynomial in a list.
% TODO: not everything is a +, there are -
%
polynomial_to_list(L + T, [T | LS]) :-
term(T),
polynomial_to_list(L, LS).
% The others computations are semantically meaningless
%% !.
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(P, [2]).
%@ P = 2 .
%%?- polynomial_to_list(P, [x]).
%@ P = x .
%%?- polynomial_to_list(P, [x^2, x, -2.3]).
%@ P = -2.3+x+x^2 .
%% append_two_atoms_with_star(+V1, +V2, -R) is det
%
% Returns R = V1 * V2
%
append_two_atoms_with_star(V1, V2, R) :-
2018-11-21 15:23:35 +00:00
% Convert term V2 into a string V3
term_string(V2, V3),
2018-11-21 15:23:35 +00:00
% Concat atom V1 with * into a compound V4
atom_concat(V1, *, V4),
2018-11-21 15:23:35 +00:00
% Concat atom V4 with V3 into a compound S
atom_concat(V4, V3, S),
2018-11-21 15:23:35 +00:00
% Convert compound S into a term R
term_string(R, S).
%% Tests:
2018-11-21 15:23:35 +00:00
% ?- append_two_atoms_with_star(2, x^2, R).
%@ R = 2*x^2.
%@ R = 2*x^2.
%@ R = 2*3.
%% scale_polynomial(+P:polynomial,+C:constant,-S:polynomial) is det
%
% Scales a polynomial with a constant
%
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).
2018-11-21 15:23:35 +00:00
%% Tests:
%% ?- scale_polynomial(3*x^2, 2, S).
%@ S = 2*3*x^2.
%@ S = 2*(3*x^2).
2018-11-22 17:49:55 +00:00
/* CENAS DO PROF: */
2018-11-18 16:33:09 +00:00
%% monomial_parts(X, Y, Z)
%
2018-11-19 16:59:53 +00:00
% TODO Maybe remove
% Separate monomial into it's parts. Given K*X^N, gives K and N
2018-11-18 16:33:09 +00:00
%
2018-11-17 16:14:13 +00:00
monomial_parts(X, 1, X) :-
2018-11-18 16:33:09 +00:00
power(X),
!.
2018-11-17 16:14:13 +00:00
monomial_parts(X^N, 1, X^N) :-
2018-11-18 16:33:09 +00:00
power(X^N),
!.
2018-11-17 16:14:13 +00:00
monomial_parts(K * M, K, M) :-
2018-11-18 16:33:09 +00:00
number(K),
!.
2018-11-17 16:14:13 +00:00
monomial_parts(K, K, indep) :-
2018-11-18 16:33:09 +00:00
number(K),
!.
2018-11-17 16:14:13 +00:00
delete_monomial(M, X, M, 0) :-
2018-11-18 23:18:28 +00:00
term(M),
2018-11-18 16:33:09 +00:00
monomial_parts(M, _, X),
!.
2018-11-17 16:14:13 +00:00
delete_monomial(M + M2, X, M, M2) :-
2018-11-18 23:18:28 +00:00
term(M2),
term(M),
2018-11-18 16:33:09 +00:00
monomial_parts(M, _, X),
!.
2018-11-17 16:14:13 +00:00
delete_monomial(P + M, X, M, P) :-
2018-11-18 23:18:28 +00:00
term(M),
2018-11-18 16:33:09 +00:00
monomial_parts(M, _, X),
!.
2018-11-17 16:14:13 +00:00
delete_monomial(P + M2, X, M, P2 + M2) :-
delete_monomial(P, X, M, P2).
add_monomial(K1, K2, K3) :-
2018-11-18 16:33:09 +00:00
number(K1),
number(K2), !,
2018-11-17 16:14:13 +00:00
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),
2018-11-18 16:33:09 +00:00
P==P2,
!.
2018-11-17 16:14:13 +00:00
closure_simplify_polynomial(P, P3) :-
simplify_polynomial(P, P2),
2018-11-18 16:33:09 +00:00
closure_simplify_polynomial(P2, P3),
!.