This commit is contained in:
Hugo Sales 2018-11-23 14:56:01 +00:00
parent 200eec49ef
commit 7c46025c13
2 changed files with 85 additions and 19 deletions

View File

@ -6,9 +6,10 @@
%% 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
%% For instance, integer(N) is always false, which prevents the
%% reversing of a predicate.
:- use_module(library(clpfd)).
%% :- use_module(library(clpr)).
%% polynomial_variable_list(-List) is det
%
@ -69,8 +70,13 @@ power(X) :-
% Returns true if N is a term, false otherwise.
%
term(N) :-
number(N).
%% N in inf..sup.
(nonvar(N),
number(N));
(not(compound(N)), var(N),
N in inf..sup).
%% {N >= -1000, N =< 1000}.
%% N ::= inf..sup.
%% (var(N), N in inf..sup).
term(X) :-
power(X).
term(L * R) :-
@ -91,6 +97,30 @@ term(L * R) :-
%% ?- term(3.2*x).
%@ 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 = 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
%% The ic library seems to be able to help here, but it's not a part of
%% SwiPL by default
@ -278,17 +308,8 @@ simplify_polynomial(0, 0) :-
!.
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),
polynomial_to_list(P2, L11),
simplify_polynomial_as_list(L, L2),
polynomial_to_list(P2, L2),
!.
%% Tests:
%% ?- simplify_polynomial(1, X).
@ -389,12 +410,21 @@ add_terms([NL | TL], [NR | TR], [N2 | TL2]) :-
%% ?- add_terms([2, x^3], [3, x^3], R).
%@ R = [5, x^3].
%% simplify_polynomial_list(+L1,-L3) is det
%% simplify_polynomial_as_list(+L1,-L3) is det
%
% Simplifies a list of polynomials
%
simplify_polynomial_list(L, L2) :-
maplist(simplify_polynomial, L, L2).
simplify_polynomial_as_list(L, L11) :-
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).
%% polynomial_to_list(+P:polynomial, -L:List)
%
@ -428,6 +458,22 @@ polynomial_to_list(T, [T]) :-
%% ?- polynomial_to_list(P, [x]).
%@ P = x .
%% ?- polynomial_to_list(P, [x^2, x, 2.3]).
%@ ERROR: Type error: `integer' expected, found `_10776*_10778' (a compound)
%@ ERROR: In:
%@ ERROR: [16] throw(error(type_error(integer,...),_10828))
%@ ERROR: [14] clpfd:attr_unify_hook(clpfd_attr(no,no,no,from_to(inf,sup),fd_props([],[],[])),_10896*_10898) at /usr/lib/swipl-7.6.4/library/clp/clpfd.pl:7127
%@ ERROR: [13] '$attvar':uhook(clpfd,clpfd_attr(no,no,no,from_to(inf,sup),fd_props([],[],[])),_10962*_10964) at /usr/lib/swipl-7.6.4/boot/attvar.pl:86
%@ ERROR: [12] '$attvar':call_all_attr_uhooks(att(clpfd,clpfd_attr(no,no,no,...,...),[]),_11020*_11022) at /usr/lib/swipl-7.6.4/boot/attvar.pl:63
%@ ERROR: [11] '$attvar':'$wakeup'(wakeup(att(clpfd,...,[]),_11072*_11074,[])) at /usr/lib/swipl-7.6.4/boot/attvar.pl:58
%@ ERROR: [10] term_to_list(_11104*_11106,[_11110|_11112]) at /tmp/ediprologEjek6K:198
%@ ERROR: [9] negate_term(_11142*_11144,x^2) at /tmp/ediprologEjek6K:470
%@ ERROR: [8] polynomial_to_list(_11180-_11186*_11188,[x^2,x|...]) at /tmp/ediprologEjek6K:436
%@ ERROR: [7] <user>
%@ ERROR:
%@ ERROR: Note: some frames are missing due to last-call optimization.
%@ ERROR: Re-run your program in debug mode (:- debug.) to get more detail.
%@ Exception: (10) term_to_list(_9692{clpfd = ...}, _11268) ? abort
%@ % Execution Aborted
%@ Action (h for help) ? abort
%@ % Execution Aborted
%@ P = -2.3+x+x^2 .
@ -482,14 +528,32 @@ append_two_atoms_with_star(V1, V2, R) :-
%
scale_polynomial(P, C, S) :-
polynomial_to_list(P, L),
maplist(append_two_atoms_with_star(C), L, L2),
list_to_polynomial(L2, S).
maplist(term_to_list, L, L2),
maplist(cons(C), L2, L3),
maplist(term_to_list, L4, L3),
%% maplist(append_two_atoms_with_star(C), L, L2),
simplify_polynomial_as_list(L4, L5),
list_to_polynomial(L5, S).
%simplify_polynomial(S1, S).
%% Tests:
%% ?- scale_polynomial(3*x^2, 2, S).
%@ ERROR: Undefined procedure: list_to_polynomial/2
%@ ERROR: In:
%@ ERROR: [9] list_to_polynomial([6* ...],_32496)
%@ ERROR: [8] scale_polynomial(3*x^2,2,_32536) at /tmp/ediprologEjek6K:536
%@ ERROR: [7] <user>
%@ Exception: (9) list_to_polynomial([6*x^2], _30888) ? abort
%@ % Execution Aborted
%@ S = [[2, x^2, 3]] .
%@ S = [[3, x^2, 3]] .
%@ false.
%@ S = [[_21808, x^2, 3]] ;
%@ false.
%@ S = 2*3*x^2.
%@ S = 2*(3*x^2).
cons(C, L, [C | L]).
%% monomial_parts(X, Y, Z)
%
% TODO Maybe remove

2
test.pl Normal file
View File

@ -0,0 +1,2 @@
:- use_module(library(clpfd)).
foo(N) :- (nonvar(N), number(N));(var(N), N in inf..sup).