diff --git a/polimani.pl b/polimani.pl index bca9745..3f0be09 100644 --- a/polimani.pl +++ b/polimani.pl @@ -1,4 +1,5 @@ %% -*- 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 @@ -9,7 +10,7 @@ %% reversing of a predicate. :- use_module(library(clpfd)). -%% polynomial_variable_list(-List:atom) is det +%% polynomial_variable_list(-List) is det % % List of possible polynomial variables % @@ -22,30 +23,23 @@ 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^N, -%% N == 1. %% Tests: %% ?- polynomial_variable(x). %@ true . -%% ?- polynomial_variable(x^(1)). +%% ?- polynomial_variable(a). %@ false. %% power(+X:atom) is semidet % % Returns true if X is a power term, false otherwise. -% Fully reversible. % power(P^N) :- - %% CPL(FD) library predicate to perform integer comparassions in a reversible way - %% If 0 > N succeds, fail, otherwise check if X is a valid variable - (zcompare((<), 0, N), polynomial_variable(P)); fail. - %% if(zcompare((>), 0, N), - %% fail, - %% polynomial_variable(X) - %% ). +( + zcompare((<), 0, N), + polynomial_variable(P) +; + fail +). power(X) :- polynomial_variable(X). %% Tests: @@ -54,42 +48,14 @@ power(X) :- %% ?- power(x^1). %@ true . %% ?- power(x^3). -%@ false. -%@ false. -%@ false. -%@ true . %@ true . %% ?- power(x^(-3)). -%@ false. -%@ false. -%@ true . -%@ false. -%@ true . -%@ false. +%@ error. %% ?- power(X). %@ X = x ; %@ X = y ; %@ X = z. -%% if(+P, -T, -F) is det -% -% A simple implementation of an if predicate. -% Returns T if P is true -% or F if P otherwise -% -%% if(If_1, Then_0, Else_0) :- -%% call(If_1, T), -%% ( T == true -> call(Then_0) -%% ; T == false -> call(Else_0) -%% ; nonvar(T) -> throw(error(type_error(boolean,T),_)) -%% ; /* var(T) */ throw(error(instantiation_error,_)) -%% ). -if(P, T, F) :- (P == true, T); F. -%% ?- if(true, N = 1, N = 2). -%@ N = 1 . -%% ?- if(false, N = 1, N = 2). -%@ N = 2. - %% term(+N:atom) is det % % Returns true if N is a term, false otherwise. @@ -116,17 +82,17 @@ term(L * R) :- % predicate the problem ocurred. % is_term_valid_in_predicate(T, F) :- -( + ( term(T) -; + ; write("Invalid term in "), write(F), write(": "), write(T), fail -). + ). %% Tests: -%% ?- is_term_valid_in_predicate(1, "Foo"). +%% ?- is_term_valid_in_predicate(1, "Chuck Norris"). %@ true . %% polynomial(+M:atom) is det @@ -259,20 +225,24 @@ join_like_terms([], []). %% 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)"), + %is_term_valid_in_predicate(M, "simplify_polynomial(M, M2)"), + term(M), %% If so, simplify it. simplify_term(M, M2), !. simplify_polynomial(P + 0, P) :- %% Ensure valid term - is_term_valid_in_predicate(P, "simplify_polynomial(P + 0, P)"), + %is_term_valid_in_predicate(P, "simplify_polynomial(P + 0, P)"), + term(P), !. simplify_polynomial(0 + P, P) :- %% Ensure valid term - is_term_valid_in_predicate(P, "simplify_polynomial(0 + P, P)"), + %is_term_valid_in_predicate(P, "simplify_polynomial(0 + P, P)"), + term(P), !. simplify_polynomial(P + M, P2 + M2) :- simplify_polynomial(P, P2), @@ -295,7 +265,6 @@ simplify_polynomial(P + M, P2 + M2) :- % % Simplifies a list of polynomials % - simplify_polynomial_list([L1], L3) :- simplify_polynomial(L1, L2), L3 = [L2]. @@ -306,6 +275,75 @@ simplify_polynomial_list([L1|L2],L3) :- % There is nothing further to compute at this point !. +%% 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]. +%% Tests: +%%?- polynomial_to_list(2*x^2+5+y*2, S). +%@S = [y*2, 5, 2*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 + ; + P = T1 + ), + % The others computations are semantically meaningless + !. +list_to_polynomial(T, P) :- + P = T. +%% Tests: +%% TODO + +%% append_two_atoms_with_star(+V1, +V2, -R) is det +% +% Returns R = V1 * V2 +% +append_two_atoms_with_star(V1, V2, R) :- + % Convert term V2 into a string V3 + term_string(V2, V3), + % Concat atom V1 with * into a compound V4 + atom_concat(V1, *, V4), + % Concat atom V4 with V3 into a compound S + atom_concat(V4, V3, S), + % Convert compound S into a term R + term_string(R, S). +%% Tests: +% ?- 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). +%% Tests: +%% ?- scale_polynomial(3*x^2, 2, S). +%@ S = 2*3*x^2. +%@ S = 2*(3*x^2). + %% monomial_parts(X, Y, Z) % % TODO Maybe remove