diff --git a/polimani.pl b/polimani.pl index acb7a89..3f0be09 100644 --- a/polimani.pl +++ b/polimani.pl @@ -3,11 +3,17 @@ %% Follows 'Coding guidelines for Prolog' - Theory and Practice of Logic Programming %% https://doi.org/10.1017/S1471068411000391 -%% polynomial_variable_list(-List:atom) is det +%% 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)). + +%% polynomial_variable_list(-List) is det % % List of possible polynomial variables % - polynomial_variable_list([x, y, z]). %% polynomial_variable(?X:atom) is det @@ -17,28 +23,38 @@ polynomial_variable_list([x, y, z]). polynomial_variable(X) :- polynomial_variable_list(V), member(X, V). -polynomial_variable(P) :- - polynomial_variable_list(V), - member(X, V), - P = X^_. %% Tests: -%% ?- term_to_list(X, [x^4]). -%@ X = x^4 . +%% ?- polynomial_variable(x). +%@ true . +%% ?- polynomial_variable(a). +%@ false. -%% power(+X:atom) is det +%% power(+X:atom) is semidet % % Returns true if X is a power term, false otherwise. % +power(P^N) :- +( + zcompare((<), 0, N), + polynomial_variable(P) +; + fail +). power(X) :- polynomial_variable(X). -power(X^N) :- - polynomial_variable(X), - integer(N), - N >= 1. %% Tests: +%% ?- power(x). +%@ true . %% ?- power(x^1). %@ true . - +%% ?- power(x^3). +%@ true . +%% ?- power(x^(-3)). +%@ error. +%% ?- power(X). +%@ X = x ; +%@ X = y ; +%@ X = z. %% term(+N:atom) is det % @@ -50,10 +66,14 @@ term(X) :- power(X). term(L * R) :- term(L), - term(R), - !. + term(R). %% Tests: -%% TODO +%% ?- term(2*x^3). +%@ true . +%% ?- term(x^(-3)). +%@ false. +%% ?- term((-3)*x^2). +%@ true . %% is_term_valid_in_predicate(+T, +F) is det % @@ -72,7 +92,8 @@ is_term_valid_in_predicate(T, F) :- fail ). %% Tests: -%% ?- is_term_valid_in_predicate(). +%% ?- is_term_valid_in_predicate(1, "Chuck Norris"). +%@ true . %% polynomial(+M:atom) is det % @@ -84,22 +105,37 @@ polynomial(L + R) :- polynomial(L), term(R). %% Tests: -%% TODO +%% ?- polynomial(x). +%@ true . +%% ?- polynomial(x^3). +%@ true . +%% ?- polynomial(3*x^7). +%@ true . +%% ?- polynomial(2 + 3*x + 4*x*y^3). +%@ true . %% power_to_canon(+T:atom, -T^N:atom) is det % % Returns a canon power term. % power_to_canon(T^N, T^N) :- - polynomial_variable(T). + polynomial_variable(T), + %% N \= 1. + ( + zcompare(=, 1, N) + ; + true + ). power_to_canon(T, T^1) :- polynomial_variable(T). %% Tests: %% ?- power_to_canon(x, X). -%@ X = x^1. -%% ?- power_to_canon(X, X^1). +%@ X = x^1 . +%% ?- power_to_canon(X, x^1). %@ X = x . -%@ X = x. +%@ X = x . +%% ?- power_to_canon(X, x^4). +%@ X = x^4 . %% term_to_list(?T, ?List) is det % @@ -119,38 +155,44 @@ term_to_list(P, [P2]) :- power(P), power_to_canon(P, P2). %% Tests: -%% ?- term_to_list(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] . +%% ?- 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, [y^1, x^1]). %@ X = x*y . %% ?- term_to_list(X, [x^4]). -%@ X = x^4 . %@ false. +%@ false. +%@ X = x^4 . %% ?- term_to_list(X, [y^6, z^2, x^4]). %@ X = x^4*z^2*y^6 . -%% simplify_term(+T:atom, -P) is det +%% simplify_term(+Term_In:term, ?Term_Out:term) is det % % Simplifies a term. % -simplify_term(1 * P, P). -simplify_term(0 * _, 0). -simplify_term(T, T2) :- - term_to_list(T, L), +simplify_term(Term_In, Term_Out) :- + term_to_list(Term_In, L), sort(0, @=<, L, L2), - join_like_terms(L2, L3), - list_to_term(L3, T2). % Responsible for parenthesis -%% sort(0, @>=, L3, L4), -%% term_to_list(T2, L4). +( + member(0, L2), + Term_Out = 0 +; + exclude(==(1), L2, L3), + join_like_terms(L3, L4), + sort(0, @>=, L4, L5), + term_to_list(Term_Out, L5) +), + % First result is always the most simplified form. + !. %% Tests: %% ?- simplify_term(2*y*z*x^3*x, X). -%@ X = 2*(x^4*(y*z)). -%@ X = z*(y*(x^4*2)). -%% ?- simplify_term(2*y*z*23*x*y*x^3*x, X). -%@ X = 46*(x^2*(x^3*(y^2*z))). -%@ X = z*(y^2*(x^3*(x^2*46))). -%@ X = [2, 23, x^1, x^3, y^1, z^1]. -%@ X = [46, x^4, y^1, z^1]. +%@ 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. %% join_like_terms(+List, -List) % @@ -214,7 +256,10 @@ simplify_polynomial(P + M, P2 + M2) :- simplify_polynomial(P, P2), simplify_term(M, M2). %% Tests: -%% TODO +%% ?- simplify_polynomial(1, 1). +%@ Invalid term in simplify_polynomial(M, M2): 1 +%@ false. + %% simplify_polynomial_list(+L1,-L3) is det %