Merge branch 'nlp-ph' into nlp
This commit is contained in:
commit
74d9e9cc5b
594
polymani.pl
594
polymani.pl
@ -34,7 +34,301 @@
|
|||||||
:- use_module(library(clpr)).
|
:- use_module(library(clpr)).
|
||||||
|
|
||||||
/*******************************
|
/*******************************
|
||||||
* USER INTERFACE *
|
* NLP *
|
||||||
|
*******************************/
|
||||||
|
|
||||||
|
%% polyplay() is det
|
||||||
|
%
|
||||||
|
% Interactive prompt for the NLP Interface
|
||||||
|
%
|
||||||
|
polyplay :-
|
||||||
|
prompt(OldPrompt, '> '),
|
||||||
|
read_string(user_input, "\n", "\r\t ", _, In),
|
||||||
|
prompt(_, OldPrompt),
|
||||||
|
split_string(In, " ", "", LS),
|
||||||
|
maplist(string_to_atom, LS, LA),
|
||||||
|
(
|
||||||
|
LA == [bye],
|
||||||
|
write("See ya"),
|
||||||
|
!
|
||||||
|
;
|
||||||
|
(
|
||||||
|
parse_input(TIn, LA, NC),
|
||||||
|
(
|
||||||
|
TIn == void,
|
||||||
|
writeln("I didn't understand what you want."),
|
||||||
|
writeln(NC)
|
||||||
|
;
|
||||||
|
process_input(TIn)
|
||||||
|
)
|
||||||
|
;
|
||||||
|
writeln("I didn't understand what you want.")
|
||||||
|
),
|
||||||
|
polyplay
|
||||||
|
),
|
||||||
|
!.
|
||||||
|
%% Tests:
|
||||||
|
%% ?- polyplay.
|
||||||
|
|
||||||
|
%% nlp_number(?W:Atom, ?D:Int) is det
|
||||||
|
%
|
||||||
|
% Definition of a Alphabetical and Numerical relation
|
||||||
|
%
|
||||||
|
special_word_number(zero, 0, f).
|
||||||
|
special_word_number(a, 1, f).
|
||||||
|
special_word_number(one, 1, f).
|
||||||
|
special_word_number(two, 2, f).
|
||||||
|
special_word_number(three, 3, f).
|
||||||
|
special_word_number(four, 4, f).
|
||||||
|
special_word_number(five, 5, f).
|
||||||
|
special_word_number(six, 6, f).
|
||||||
|
special_word_number(seven, 7, f).
|
||||||
|
special_word_number(eight, 8, f).
|
||||||
|
special_word_number(nine, 9, f).
|
||||||
|
special_word_number(ten, 10, g).
|
||||||
|
special_word_number(eleven, 11, g).
|
||||||
|
special_word_number(twelve, 12, g).
|
||||||
|
special_word_number(thirteen, 13, g).
|
||||||
|
special_word_number(fourteen, 14, g).
|
||||||
|
special_word_number(fifteen, 15, g).
|
||||||
|
special_word_number(sixteen, 16, g).
|
||||||
|
special_word_number(seventeen, 17, g).
|
||||||
|
special_word_number(eighteen, 18, g).
|
||||||
|
special_word_number(nineteen, 19, g).
|
||||||
|
special_word_number(twenty, 20, fy).
|
||||||
|
special_word_number(thirty, 30, fy).
|
||||||
|
special_word_number(forty, 40, fy).
|
||||||
|
special_word_number(fifty, 50, fy).
|
||||||
|
special_word_number(sixty, 60, fy).
|
||||||
|
special_word_number(seventy, 70, fy).
|
||||||
|
special_word_number(eighty, 80, fy).
|
||||||
|
special_word_number(ninety, 90, fy).
|
||||||
|
special_word_number(hundred, 100, xfy).
|
||||||
|
special_word_number(thousand, 1000, xfy).
|
||||||
|
special_word_number(million, 1000000, xfy).
|
||||||
|
|
||||||
|
%% nlp_number(?W:Atom, ?D:Int) is det
|
||||||
|
%
|
||||||
|
% Definition of a Alphabetical and Numerical relation
|
||||||
|
%
|
||||||
|
|
||||||
|
%% Entry point
|
||||||
|
parse_number_explicit(void, void, T, [WN | In], NC) :-
|
||||||
|
special_word_number(WN, N, P),
|
||||||
|
member(P, [f, g, fy]),
|
||||||
|
!,
|
||||||
|
parse_number_explicit(P, N, T, In, NC).
|
||||||
|
parse_number_explicit(fy, NL, T, [WN | In], NC) :-
|
||||||
|
special_word_number(WN, N, f),
|
||||||
|
!,
|
||||||
|
parse_number_explicit(f, op(+, NL, N), T, In, NC).
|
||||||
|
parse_number_explicit(xfy, TL, T, [WN | In], NC) :-
|
||||||
|
TL \= void,
|
||||||
|
special_word_number(WN, N, P),
|
||||||
|
member(P, [f, g, fy]),
|
||||||
|
!,
|
||||||
|
parse_number_explicit(P, op(+, TL, N), T, In, NC).
|
||||||
|
parse_number_explicit(_, TL, T, [WN | In], NC) :-
|
||||||
|
special_word_number(WN, N, xfy),
|
||||||
|
TL \= void,
|
||||||
|
!,
|
||||||
|
parse_number_explicit(xfy, op(*, TL, N), T, In, NC).
|
||||||
|
parse_number_explicit(P, TL, T, [and, WN | In], NC) :-
|
||||||
|
special_word_number(WN, _, _),
|
||||||
|
parse_number_explicit(P, TL, T, [WN | In], NC),
|
||||||
|
!.
|
||||||
|
parse_number_explicit(_, T, T, [WN | In], [WN | In]) :-
|
||||||
|
T \= void,
|
||||||
|
not(special_word_number(WN, _, _)),
|
||||||
|
!.
|
||||||
|
parse_number_explicit(_, T, T, [], []) :-
|
||||||
|
T \= void,
|
||||||
|
!.
|
||||||
|
|
||||||
|
parse_number(T, SL, NC) :-
|
||||||
|
parse_number_explicit(void, void, T, SL, NC).
|
||||||
|
%% Tests:
|
||||||
|
%% ?- parse_number(T, [two], _).
|
||||||
|
%@ T = 2.
|
||||||
|
%% ?- parse_number(T, [nineteen, two], _).
|
||||||
|
%@ false.
|
||||||
|
%% ?- parse_number(T, [twenty], _).
|
||||||
|
%@ T = 20.
|
||||||
|
%% ?- parse_number(T, [twenty, twenty], _).
|
||||||
|
%@ false.
|
||||||
|
%% ?- parse_number(T, [twenty, one], _).
|
||||||
|
%@ T = op(+, 20, 1).
|
||||||
|
%% ?- parse_number(T, [hundred], _).
|
||||||
|
%@ false.
|
||||||
|
%% ?- parse_number(T, [three, hundred], _).
|
||||||
|
%@ T = op(*, 3, 100).
|
||||||
|
%% ?- parse_number(T, [twenty, hundred], _).
|
||||||
|
%@ T = op(*, 20, 100).
|
||||||
|
%% ?- parse_number(T, [twenty, one, hundred], _).
|
||||||
|
%@ T = op(*, op(+, 20, 1), 100).
|
||||||
|
%% ?- parse_number(T, [two, hundred, and, one], _).
|
||||||
|
%@ T = op(+, op(*, 2, 100), 1).
|
||||||
|
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one], _).
|
||||||
|
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1).
|
||||||
|
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one, foo, bar, blah], NC).
|
||||||
|
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1),
|
||||||
|
%@ NC = [foo, bar, blah].
|
||||||
|
%% ?- parse_number(T, [twenty, one, hundred, and, bleg, twenty, quux, one, foo, bar], NC).
|
||||||
|
%@ T = op(*, op(+, 20, 1), 100),
|
||||||
|
%@ NC = [and, bleg, twenty, quux, one, foo, bar].
|
||||||
|
%% ?- parse_number(T, [two, hundred, thousand], _).
|
||||||
|
%@ T = op(*, op(*, 2, 100), 1000).
|
||||||
|
%% ?- parse_number(T, [twenty, one, hundred, thousand], _).
|
||||||
|
%@ T = op(*, op(*, op(+, 20, 1), 100), 1000).
|
||||||
|
%% ?- parse_number(T, [thirty, five, million, five, hundred, thirty, four], _).
|
||||||
|
%@ T = op(+, op(+, op(*, op(+, op(*, op(+, 30, 5), 1000000), 5), 100), 30), 4).
|
||||||
|
%% ?- parse_number(T, [foo, five, million], NC).
|
||||||
|
%@ false.
|
||||||
|
|
||||||
|
%% nlp_parse_power(?List, ?List) is det
|
||||||
|
%
|
||||||
|
% Parse powers
|
||||||
|
%
|
||||||
|
%% Order matters
|
||||||
|
parse_power(op(^, TB, 2)) -->
|
||||||
|
parse_polynomial_variable(TB),
|
||||||
|
[squared].
|
||||||
|
parse_power(op(^, TB, 3)) -->
|
||||||
|
parse_polynomial_variable(TB),
|
||||||
|
[cubed].
|
||||||
|
parse_power(op(^, TB, TN)) -->
|
||||||
|
parse_polynomial_variable(TB),
|
||||||
|
[raised, to],
|
||||||
|
parse_number(TN).
|
||||||
|
parse_power(TB) -->
|
||||||
|
parse_polynomial_variable(TB).
|
||||||
|
|
||||||
|
|
||||||
|
parse_operation(+) --> [plus].
|
||||||
|
parse_operation(*) --> [times].
|
||||||
|
|
||||||
|
parse_polynomial_operand(T) --> parse_number(T).
|
||||||
|
parse_polynomial_operand(T) --> parse_power(T).
|
||||||
|
parse_polynomial_operand(T) --> parse_stored_variable(T).
|
||||||
|
|
||||||
|
:- dynamic polynomial_store/2.
|
||||||
|
|
||||||
|
parse_stored_variable(load(P)) --> %% NOTE Not sure if it's better to load now or later
|
||||||
|
[P],
|
||||||
|
{ polynomial_store(P, _) }.
|
||||||
|
|
||||||
|
parse_polynomial_variable(B) -->
|
||||||
|
[B],
|
||||||
|
{ polynomial_variable(B) }.
|
||||||
|
|
||||||
|
parse_polynomial(T, NC, NC) :-
|
||||||
|
not(parse_polynomial_explicit(_-_, T, NC, _)),
|
||||||
|
!.
|
||||||
|
parse_polynomial(T) -->
|
||||||
|
parse_polynomial_explicit(_-_, T).
|
||||||
|
|
||||||
|
parse_polynomial_explicit(void-_, T) -->
|
||||||
|
parse_polynomial_operand(TL),
|
||||||
|
parse_operation(Op),
|
||||||
|
!,
|
||||||
|
parse_polynomial_explicit(op(Op, TL, TRP)-TRP, T).
|
||||||
|
parse_polynomial_explicit(TLP-TL, T) -->
|
||||||
|
parse_polynomial_operand(TL),
|
||||||
|
parse_operation(+),
|
||||||
|
!,
|
||||||
|
parse_polynomial_explicit(op(+, TLP, TRP)-TRP, T).
|
||||||
|
parse_polynomial_explicit(TLP-T, TLP) -->
|
||||||
|
parse_polynomial_operand(TL),
|
||||||
|
parse_operation(*),
|
||||||
|
!,
|
||||||
|
parse_polynomial_explicit(op(*, TL, TRP)-TRP, T).
|
||||||
|
parse_polynomial_explicit(TLP-TL, TLP) -->
|
||||||
|
{ TLP \= void },
|
||||||
|
parse_polynomial_operand(TL),
|
||||||
|
!,
|
||||||
|
{ TL \= void }.
|
||||||
|
parse_polynomial_explicit(void-_, T) -->
|
||||||
|
parse_polynomial_operand(T),
|
||||||
|
!,
|
||||||
|
{ T \= void }.
|
||||||
|
%% Tests:
|
||||||
|
%% ?- parse_polynomial(T, [], _).
|
||||||
|
%@ false.
|
||||||
|
%% ?- parse_polynomial(T, [two], _).
|
||||||
|
%@ T = 2.
|
||||||
|
%% ?- parse_polynomial(T, [two, times, three], _).
|
||||||
|
%@ T = op(*, 2, 3).
|
||||||
|
%% ?- parse_polynomial(T, [two, times, three, plus, four], _).
|
||||||
|
%@ T = op(+, op(*, 2, 3), 4).
|
||||||
|
%% ?- parse_polynomial(T, [two, plus, three, times, four], _).
|
||||||
|
%@ T = op(+, 2, op(*, 3, 4)).
|
||||||
|
%% ?- parse_polynomial(T, [two, plus, three, times, four, plus, six, times, five], _).
|
||||||
|
%@ T = op(+, 2, op(+, op(*, 3, 4), op(*, 6, 5))).
|
||||||
|
%% ?- parse_polynomial(T, [two, times, times, two], NC); write(NC).
|
||||||
|
%@ NC = [two, times, times, two] ;
|
||||||
|
%@ _2006
|
||||||
|
%@ true. %% NOTE Potential problem. It seems NC isn't unified with the list, if it fails
|
||||||
|
%% ?- parse_polynomial(T, [two, plus, x, times, four], _).
|
||||||
|
%@ T = op(+, 2, op(*, x, 4)).
|
||||||
|
%% ?- parse_polynomial(T, [two, plus, x, times, four, plus, y, raised, to, five], _).
|
||||||
|
%@ T = op(+, 2, op(+, op(*, x, 4), op(^, y, 5))).
|
||||||
|
%% ?- parse_polynomial(T, [two, plus, two, plus, one, times, y], _).
|
||||||
|
%@ T = op(+, op(+, 2, 2), op(*, 1, y)).
|
||||||
|
|
||||||
|
|
||||||
|
parse_command(show(void, T)) --> %% NOTE Probably easier if the tree is always binary
|
||||||
|
[show],
|
||||||
|
parse_polynomial_explicit(T).
|
||||||
|
parse_command(show(P, T)) -->
|
||||||
|
[show],
|
||||||
|
parse_polynomial_explicit(T),
|
||||||
|
[as],
|
||||||
|
[P].
|
||||||
|
parse_command(show_all) -->
|
||||||
|
[show, stored, polynomials].
|
||||||
|
parse_command(store(P, T)) -->
|
||||||
|
[let],
|
||||||
|
[P],
|
||||||
|
[be],
|
||||||
|
parse_polynomial_explicit(T).
|
||||||
|
parse_command(store(P, T)) -->
|
||||||
|
[store],
|
||||||
|
parse_polynomial_explicit(T),
|
||||||
|
[as],
|
||||||
|
[P].
|
||||||
|
parse_command(simplify(T)) -->
|
||||||
|
[simplify],
|
||||||
|
parse_polynomial_explicit(T).
|
||||||
|
parse_command(op(*, TN, TP)) -->
|
||||||
|
[multiply],
|
||||||
|
parse_number(TN),
|
||||||
|
[by],
|
||||||
|
parse_polynomial_explicit(_-_, TP).
|
||||||
|
|
||||||
|
parse_input(command(TCL, TCR)) -->
|
||||||
|
parse_command(TCL),
|
||||||
|
[and],
|
||||||
|
!,
|
||||||
|
parse_input(TCR).
|
||||||
|
parse_input(TC) -->
|
||||||
|
parse_command(TC).
|
||||||
|
parse_input(void, [], _).
|
||||||
|
|
||||||
|
|
||||||
|
%% nlp_print_memory
|
||||||
|
%
|
||||||
|
% Prints the NLP memory
|
||||||
|
%
|
||||||
|
nlp_print_memory([nm(X,Y)|T]) :-
|
||||||
|
write(X),
|
||||||
|
write(" = "),
|
||||||
|
writeln(Y),
|
||||||
|
nlp_print_memory(T).
|
||||||
|
nlp_print_memory([]).
|
||||||
|
|
||||||
|
|
||||||
|
/*******************************
|
||||||
|
* UI *
|
||||||
*******************************/
|
*******************************/
|
||||||
|
|
||||||
/*
|
/*
|
||||||
@ -153,248 +447,6 @@ is_number_valid_in_predicate(C, F) :-
|
|||||||
fail.
|
fail.
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
/*******************************
|
|
||||||
* NLP *
|
|
||||||
*******************************/
|
|
||||||
|
|
||||||
%% polyplay() is det
|
|
||||||
%
|
|
||||||
% Interactive prompt for the NLP Interface
|
|
||||||
%
|
|
||||||
polyplay :-
|
|
||||||
prompt(Old, '> '),
|
|
||||||
read_string(user_input, "\n", "\r\t ", _, Stdin),
|
|
||||||
prompt(_, Old),
|
|
||||||
string_lower(Stdin, Stdin_lower),
|
|
||||||
split_string(Stdin_lower, " ", "", LS),
|
|
||||||
maplist(string_to_atom, LS, R),
|
|
||||||
(
|
|
||||||
R == [bye],
|
|
||||||
write("See ya"),
|
|
||||||
!
|
|
||||||
;
|
|
||||||
(
|
|
||||||
nlp_handler(R, Z),
|
|
||||||
writeln(Z)
|
|
||||||
;
|
|
||||||
writeln("I didn't understand what you want.")
|
|
||||||
),
|
|
||||||
polyplay
|
|
||||||
),
|
|
||||||
!.
|
|
||||||
|
|
||||||
%% nlp_number(?W:Atom, ?D:Int) is det
|
|
||||||
%
|
|
||||||
% Definition of a Alphabetical and Numerical relation
|
|
||||||
%
|
|
||||||
special_word_number(zero, 0, f).
|
|
||||||
special_word_number(a, 1, f).
|
|
||||||
special_word_number(one, 1, f).
|
|
||||||
special_word_number(two, 2, f).
|
|
||||||
special_word_number(three, 3, f).
|
|
||||||
special_word_number(four, 4, f).
|
|
||||||
special_word_number(five, 5, f).
|
|
||||||
special_word_number(six, 6, f).
|
|
||||||
special_word_number(seven, 7, f).
|
|
||||||
special_word_number(eight, 8, f).
|
|
||||||
special_word_number(nine, 9, f).
|
|
||||||
special_word_number(ten, 10, g).
|
|
||||||
special_word_number(eleven, 11, g).
|
|
||||||
special_word_number(twelve, 12, g).
|
|
||||||
special_word_number(thirteen, 13, g).
|
|
||||||
special_word_number(fourteen, 14, g).
|
|
||||||
special_word_number(fifteen, 15, g).
|
|
||||||
special_word_number(sixteen, 16, g).
|
|
||||||
special_word_number(seventeen, 17, g).
|
|
||||||
special_word_number(eighteen, 18, g).
|
|
||||||
special_word_number(nineteen, 19, g).
|
|
||||||
special_word_number(twenty, 20, fy).
|
|
||||||
special_word_number(thirty, 30, fy).
|
|
||||||
special_word_number(forty, 40, fy).
|
|
||||||
special_word_number(fifty, 50, fy).
|
|
||||||
special_word_number(sixty, 60, fy).
|
|
||||||
special_word_number(seventy, 70, fy).
|
|
||||||
special_word_number(eighty, 80, fy).
|
|
||||||
special_word_number(ninety, 90, fy).
|
|
||||||
special_word_number(hundred, 100, xfy).
|
|
||||||
special_word_number(thousand, 1000, xfy).
|
|
||||||
special_word_number(million, 1000000, xfy).
|
|
||||||
|
|
||||||
%% Entry point
|
|
||||||
parse_number_explicit(void, void, T, [WN | R], NC) :-
|
|
||||||
special_word_number(WN, N, P),
|
|
||||||
member(P, [f, g, fy]),
|
|
||||||
!,
|
|
||||||
parse_number_explicit(P, N, T, R, NC).
|
|
||||||
parse_number_explicit(fy, NL, T, [WN | R], NC) :-
|
|
||||||
special_word_number(WN, N, f),
|
|
||||||
!,
|
|
||||||
parse_number_explicit(f, op(+, NL, N), T, R, NC).
|
|
||||||
parse_number_explicit(xfy, TL, T, [WN | R], NC) :-
|
|
||||||
TL \= void,
|
|
||||||
special_word_number(WN, N, P),
|
|
||||||
member(P, [f, g, fy]),
|
|
||||||
!,
|
|
||||||
parse_number_explicit(P, op(+, TL, N), T, R, NC).
|
|
||||||
parse_number_explicit(_, TL, T, [WN | R], NC) :-
|
|
||||||
special_word_number(WN, N, xfy),
|
|
||||||
TL \= void,
|
|
||||||
!,
|
|
||||||
parse_number_explicit(xfy, op(*, TL, N), T, R, NC).
|
|
||||||
parse_number_explicit(P, TL, T, [and, WN | R], NC) :-
|
|
||||||
special_word_number(WN, _, _),
|
|
||||||
parse_number_explicit(P, TL, T, [WN | R], NC),
|
|
||||||
!.
|
|
||||||
parse_number_explicit(_, T, T, [WN | R], [WN | R]) :-
|
|
||||||
T \= void,
|
|
||||||
not(special_word_number(WN, _, _)),
|
|
||||||
!.
|
|
||||||
parse_number_explicit(_, T, T, [], []) :-
|
|
||||||
T \= void,
|
|
||||||
!.
|
|
||||||
|
|
||||||
parse_number(T, SL, NC) :-
|
|
||||||
parse_number_explicit(void, void, T, SL, NC).
|
|
||||||
%% Tests:
|
|
||||||
%% ?- parse_number(T, [two], _).
|
|
||||||
%@ T = 2.
|
|
||||||
%% ?- parse_number(T, [nineteen, two], _).
|
|
||||||
%@ false.
|
|
||||||
%% ?- parse_number(T, [twenty], _).
|
|
||||||
%@ T = 20.
|
|
||||||
%% ?- parse_number(T, [twenty, twenty], _).
|
|
||||||
%@ false.
|
|
||||||
%% ?- parse_number(T, [twenty, one], _).
|
|
||||||
%@ T = op(+, 20, 1).
|
|
||||||
%% ?- parse_number(T, [hundred], _).
|
|
||||||
%@ false.
|
|
||||||
%% ?- parse_number(T, [three, hundred], _).
|
|
||||||
%@ T = op(*, 3, 100).
|
|
||||||
%% ?- parse_number(T, [twenty, hundred], _).
|
|
||||||
%@ T = op(*, 20, 100).
|
|
||||||
%% ?- parse_number(T, [twenty, one, hundred], _).
|
|
||||||
%@ T = op(*, op(+, 20, 1), 100).
|
|
||||||
%% ?- parse_number(T, [two, hundred, and, one], _).
|
|
||||||
%@ T = op(+, op(*, 2, 100), 1).
|
|
||||||
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one], _).
|
|
||||||
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1).
|
|
||||||
%% ?- parse_number(T, [twenty, one, hundred, and, twenty, one, foo, bar, blah], NC).
|
|
||||||
%@ T = op(+, op(+, op(*, op(+, 20, 1), 100), 20), 1),
|
|
||||||
%@ NC = [foo, bar, blah].
|
|
||||||
%% ?- parse_number(T, [twenty, one, hundred, and, bleg, twenty, quux, one, foo, bar], NC).
|
|
||||||
%@ T = op(*, op(+, 20, 1), 100),
|
|
||||||
%@ NC = [and, bleg, twenty, quux, one, foo, bar].
|
|
||||||
%% ?- parse_number(T, [two, hundred, thousand], _).
|
|
||||||
%@ T = op(*, op(*, 2, 100), 1000).
|
|
||||||
%% ?- parse_number(T, [twenty, one, hundred, thousand], _).
|
|
||||||
%@ T = op(*, op(*, op(+, 20, 1), 100), 1000).
|
|
||||||
%% ?- parse_number(T, [thirty, five, million, five, hundred, thirty, four], _).
|
|
||||||
%@ T = op(+, op(+, op(*, op(+, op(*, op(+, 30, 5), 1000000), 5), 100), 30), 4).
|
|
||||||
%% ?- parse_number(T, [foo, five, million], NC).
|
|
||||||
%@ false.
|
|
||||||
|
|
||||||
parse_operation(+) --> [plus].
|
|
||||||
parse_operation(*) --> [times].
|
|
||||||
|
|
||||||
parse_polynomial_operand(T) --> parse_number(T).
|
|
||||||
parse_polynomial_operand(T) --> parse_power(T).
|
|
||||||
parse_polynomial_operand(T) --> parse_stored_variable(T).
|
|
||||||
|
|
||||||
:- dynamic polynomial_store/2.
|
|
||||||
|
|
||||||
parse_stored_variable(T) --> %% NOTE Not sure if it's better to load now or later
|
|
||||||
[P],
|
|
||||||
{ polynomial_store(P, T) }.
|
|
||||||
|
|
||||||
parse_polynomial_variable(B) -->
|
|
||||||
[B],
|
|
||||||
{ polynomial_variable(B) }.
|
|
||||||
|
|
||||||
%% Order matters
|
|
||||||
parse_power(op(^, TB, 2)) -->
|
|
||||||
parse_polynomial_variable(TB),
|
|
||||||
[squared].
|
|
||||||
parse_power(op(^, TB, 3)) -->
|
|
||||||
parse_polynomial_variable(TB),
|
|
||||||
[cubed].
|
|
||||||
parse_power(op(^, TB, TN)) -->
|
|
||||||
parse_polynomial_variable(TB),
|
|
||||||
[raised, to],
|
|
||||||
parse_number(TN).
|
|
||||||
parse_power(TB) -->
|
|
||||||
parse_polynomial_variable(TB).
|
|
||||||
|
|
||||||
parse_polynomial(void-_, T) -->
|
|
||||||
parse_polynomial_operand(TL),
|
|
||||||
parse_operation(Op),
|
|
||||||
!,
|
|
||||||
parse_polynomial(op(Op, TL, TRP)-TRP, T).
|
|
||||||
parse_polynomial(TLP-TL, T) -->
|
|
||||||
parse_polynomial_operand(TL),
|
|
||||||
parse_operation(+),
|
|
||||||
!,
|
|
||||||
parse_polynomial(op(+, TLP, TRP)-TRP, T).
|
|
||||||
parse_polynomial(TLP-T, TLP) -->
|
|
||||||
parse_polynomial_operand(TL),
|
|
||||||
parse_operation(*),
|
|
||||||
!,
|
|
||||||
parse_polynomial(op(*, TL, TRP)-TRP, T).
|
|
||||||
parse_polynomial(TLP-TL, TLP) -->
|
|
||||||
{ TLP \= void },
|
|
||||||
parse_polynomial_operand(TL),
|
|
||||||
!,
|
|
||||||
{ TL \= void }.
|
|
||||||
parse_polynomial(void-_, T) -->
|
|
||||||
parse_polynomial_operand(T),
|
|
||||||
!,
|
|
||||||
{ T \= void }.
|
|
||||||
%% Tests:
|
|
||||||
%% ?- parse_polynomial(_-_, T, [], _).
|
|
||||||
%@ false.
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two], _).
|
|
||||||
%@ T = 2.
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, times, three], _).
|
|
||||||
%@ T = op(*, 2, 3).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, times, three, plus, four], _).
|
|
||||||
%@ T = op(+, op(*, 2, 3), 4).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, plus, three, times, four], _).
|
|
||||||
%@ T = op(+, 2, op(*, 3, 4)).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, plus, three, times, four, plus, six, times, five], _).
|
|
||||||
%@ T = op(+, 2, op(+, op(*, 3, 4), op(*, 6, 5))).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, times, times, two], NC); write(NC).
|
|
||||||
%@ _3164
|
|
||||||
%@ true. %% NOTE Potential problem. It seems NC isn't unified with the list, if it fails
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, plus, x, times, four], _).
|
|
||||||
%@ T = op(+, 2, op(*, x, 4)).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, plus, x, times, four, plus, y, raised, to, five], _).
|
|
||||||
%@ T = op(+, 2, op(+, op(*, x, 4), op(^, y, 5))).
|
|
||||||
%% ?- parse_polynomial(_-_, T, [two, plus, two, plus, one, times, y], _).
|
|
||||||
%@ T = op(+, op(+, 2, 2), op(*, 1, y)).
|
|
||||||
|
|
||||||
|
|
||||||
parse_command(show(T)) --> %% NOTE Probably easier if the tree is always binary
|
|
||||||
[show],
|
|
||||||
parse_polynomial(T).
|
|
||||||
parse_command(show(store(P, T))) -->
|
|
||||||
[show],
|
|
||||||
parse_polynomial(T),
|
|
||||||
[as],
|
|
||||||
[P].
|
|
||||||
parse_command(store(P, T)) -->
|
|
||||||
[let],
|
|
||||||
[P],
|
|
||||||
[be],
|
|
||||||
parse_polynomial(T).
|
|
||||||
parse_command(simplify(T)) -->
|
|
||||||
[simplify],
|
|
||||||
parse_polynomial(T).
|
|
||||||
parse_command(op(*, TN, TP)) -->
|
|
||||||
[multiply],
|
|
||||||
parse_number(TN),
|
|
||||||
[by],
|
|
||||||
parse_polynomial(TP).
|
|
||||||
|
|
||||||
/*******************************
|
/*******************************
|
||||||
* BACKEND *
|
* BACKEND *
|
||||||
*******************************/
|
*******************************/
|
||||||
@ -474,9 +526,9 @@ term(X) :-
|
|||||||
power(X).
|
power(X).
|
||||||
term(-X) :-
|
term(-X) :-
|
||||||
power(X).
|
power(X).
|
||||||
term(L * R) :-
|
term(L * In) :-
|
||||||
term(L),
|
term(L),
|
||||||
term(R).
|
term(In).
|
||||||
%% Tests:
|
%% Tests:
|
||||||
%% ?- term(2*x^3).
|
%% ?- term(2*x^3).
|
||||||
%@ true .
|
%@ true .
|
||||||
@ -523,14 +575,14 @@ term(L * R) :-
|
|||||||
polynomial(M) :-
|
polynomial(M) :-
|
||||||
%% A polynomial is either a term
|
%% A polynomial is either a term
|
||||||
term(M).
|
term(M).
|
||||||
polynomial(L + R) :-
|
polynomial(L + In) :-
|
||||||
%% Or a sum of terms
|
%% Or a sum of terms
|
||||||
polynomial(L),
|
polynomial(L),
|
||||||
term(R).
|
term(In).
|
||||||
polynomial(L - R) :-
|
polynomial(L - In) :-
|
||||||
%% Or a subtraction of terms
|
%% Or a subtraction of terms
|
||||||
polynomial(L),
|
polynomial(L),
|
||||||
term(R).
|
term(In).
|
||||||
%% Tests:
|
%% Tests:
|
||||||
%% ?- polynomial(x).
|
%% ?- polynomial(x).
|
||||||
%@ true .
|
%@ true .
|
||||||
@ -979,7 +1031,7 @@ sign_of_power(-P, -1*P).
|
|||||||
%% ?- sign_of_power(X, -1*x).
|
%% ?- sign_of_power(X, -1*x).
|
||||||
%@ X = -x.
|
%@ X = -x.
|
||||||
|
|
||||||
%% add_terms(+L:List, +R:List, -Result:List) is det
|
%% add_terms(+L:List, +In:List, -Result:List) is det
|
||||||
%
|
%
|
||||||
% Adds two terms represented as list by adding
|
% Adds two terms represented as list by adding
|
||||||
% the coeficients if the power is the same.
|
% the coeficients if the power is the same.
|
||||||
@ -996,15 +1048,15 @@ add_terms([NL | TL], [NR | TR], [N2 | TL2]) :-
|
|||||||
%% Add the coeficients
|
%% Add the coeficients
|
||||||
N2 is NL2 + NR2.
|
N2 is NL2 + NR2.
|
||||||
%% Tests
|
%% Tests
|
||||||
%% ?- add_terms([1], [1], R).
|
%% ?- add_terms([1], [1], In).
|
||||||
%@ R = [2].
|
%@ In = [2].
|
||||||
%% ?- add_terms([x], [x], R).
|
%% ?- add_terms([x], [x], In).
|
||||||
%@ R = [2, x].
|
%@ In = [2, x].
|
||||||
%% ?- add_terms([2, x^3], [x^3], R).
|
%% ?- add_terms([2, x^3], [x^3], In).
|
||||||
%@ R = [3, x^3].
|
%@ In = [3, x^3].
|
||||||
%% ?- add_terms([2, x^3], [3, x^3], R).
|
%% ?- add_terms([2, x^3], [3, x^3], In).
|
||||||
%@ R = [5, x^3].
|
%@ In = [5, x^3].
|
||||||
%% ?- add_terms([2, x^3], [3, x^2], R).
|
%% ?- add_terms([2, x^3], [3, x^2], In).
|
||||||
%@ false.
|
%@ false.
|
||||||
|
|
||||||
%% polynomial_to_list(+P:polynomial, -L:List) is det
|
%% polynomial_to_list(+P:polynomial, -L:List) is det
|
||||||
@ -1087,28 +1139,28 @@ negate_term(T, T2) :-
|
|||||||
term_to_list(T, L),
|
term_to_list(T, L),
|
||||||
%% Ensure there is a coeficient
|
%% Ensure there is a coeficient
|
||||||
term_to_canon(L, L2),
|
term_to_canon(L, L2),
|
||||||
[N | R] = L2,
|
[N | In] = L2,
|
||||||
%% (-)/1 is an operator, needs to be evaluated, otherwise
|
%% (-)/1 is an operator, needs to be evaluated, otherwise
|
||||||
%% it gives a symbolic result, which messes with further processing
|
%% it gives a symbolic result, which messes with further processing
|
||||||
N2 is -N,
|
N2 is -N,
|
||||||
%% Convert the term back from canonic form
|
%% Convert the term back from canonic form
|
||||||
term_to_canon(L3, [N2 | R]),
|
term_to_canon(L3, [N2 | In]),
|
||||||
%% Reverse the order of the list, because converting
|
%% Reverse the order of the list, because converting
|
||||||
%% implicitly reverses it
|
%% implicitly reverses it
|
||||||
reverse(L3, L4),
|
reverse(L3, L4),
|
||||||
term_to_list(T2, L4),
|
term_to_list(T2, L4),
|
||||||
!.
|
!.
|
||||||
%% Tests:
|
%% Tests:
|
||||||
%% ?- negate_term(1, R).
|
%% ?- negate_term(1, In).
|
||||||
%@ R = -1.
|
%@ In = -1.
|
||||||
%% ?- negate_term(x, R).
|
%% ?- negate_term(x, In).
|
||||||
%@ R = -x.
|
%@ In = -x.
|
||||||
%% ?- negate_term(-x, R).
|
%% ?- negate_term(-x, In).
|
||||||
%@ R = x.
|
%@ In = x.
|
||||||
%% ?- negate_term(x^2, R).
|
%% ?- negate_term(x^2, In).
|
||||||
%@ R = -x^2.
|
%@ In = -x^2.
|
||||||
%% ?- negate_term(3*x*y^2, R).
|
%% ?- negate_term(3*x*y^2, In).
|
||||||
%@ R = -3*y^2*x.
|
%@ In = -3*y^2*x.
|
||||||
|
|
||||||
%% scale_polynomial(+P:Polynomial,+C:Constant,-S:Polynomial) is det
|
%% scale_polynomial(+P:Polynomial,+C:Constant,-S:Polynomial) is det
|
||||||
%
|
%
|
||||||
|
Reference in New Issue
Block a user