I guess polyplay now works fine...
Fixed various bugs, refactored, reorganized, simplified logic
This commit is contained in:
parent
c9a2eeca89
commit
40da15ba54
318
polymani.pl
318
polymani.pl
@ -33,10 +33,188 @@
|
|||||||
*/
|
*/
|
||||||
:- use_module(library(clpr)).
|
:- use_module(library(clpr)).
|
||||||
|
|
||||||
|
/*******************************
|
||||||
|
* NLP *
|
||||||
|
*******************************/
|
||||||
|
|
||||||
|
%% nlp_number(?W:Atom, ?D:Int) is det
|
||||||
|
%
|
||||||
|
% Definition of a Alphabetical and Numerical relation
|
||||||
|
%
|
||||||
|
nlp_number(zero, 0).
|
||||||
|
nlp_number(one, 1).
|
||||||
|
nlp_number(two, 2).
|
||||||
|
nlp_number(three, 3).
|
||||||
|
nlp_number(four, 4).
|
||||||
|
nlp_number(five, 5).
|
||||||
|
nlp_number(six, 6).
|
||||||
|
nlp_number(seven, 7).
|
||||||
|
nlp_number(eight, 8).
|
||||||
|
nlp_number(nine, 9).
|
||||||
|
nlp_number(ten, 10).
|
||||||
|
|
||||||
|
%% nlp_get_number_from_alpha(+X:String, -D:Int) is det
|
||||||
|
%
|
||||||
|
% Get number's int representation from alphabetical graciously
|
||||||
|
%
|
||||||
|
nlp_get_number_from_alpha(X, Z) :-
|
||||||
|
nlp_number(X, Z),
|
||||||
|
!.
|
||||||
|
nlp_get_number_from_alpha(X, X).
|
||||||
|
|
||||||
|
%% nlp_parse_numbers(?List, ?List) is det
|
||||||
|
%
|
||||||
|
% Parse numbers
|
||||||
|
%
|
||||||
|
nlp_parse_numbers([H|T], [N|U]) :-
|
||||||
|
nlp_get_number_from_alpha(H, N),
|
||||||
|
nlp_parse_numbers(T, U).
|
||||||
|
nlp_parse_numbers([], []).
|
||||||
|
|
||||||
|
%% nlp_parse_power(?List, ?List) is det
|
||||||
|
%
|
||||||
|
% Parse powers
|
||||||
|
%
|
||||||
|
nlp_parse_power([X, raised, to, Y | T], [K|NewT]) :-
|
||||||
|
number(X),
|
||||||
|
number(Y),
|
||||||
|
K is X ** Y,
|
||||||
|
nlp_parse_power(T, NewT),
|
||||||
|
!.
|
||||||
|
nlp_parse_power([X, raised, to, Y | T], [X^Y|NewT]) :-
|
||||||
|
number(X),
|
||||||
|
nlp_parse_power(T, NewT),
|
||||||
|
!.
|
||||||
|
nlp_parse_power([X, raised, to, Y | T], Z) :-
|
||||||
|
poly2list(X^Y, K),
|
||||||
|
nlp_parse_power(T, NewT),
|
||||||
|
append(K, NewT, Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_power([X, squared | T], Z) :-
|
||||||
|
number(X),
|
||||||
|
A is X**2,
|
||||||
|
nlp_parse_power([A|T], Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_power([X, squared | T], [X^2|Z]) :-
|
||||||
|
nlp_parse_power(T, Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_power([H|T], [H|Z]) :-
|
||||||
|
nlp_parse_power(T, Z).
|
||||||
|
nlp_parse_power([], []).
|
||||||
|
|
||||||
|
%% nlp_parse_multiplication(?List, ?List) is det
|
||||||
|
%
|
||||||
|
% Parse multiplication
|
||||||
|
%
|
||||||
|
nlp_parse_multiplication([X, times, Y | T], Z) :-
|
||||||
|
simpoly(X*Y, A),
|
||||||
|
nlp_parse_multiplication([A|T], Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_multiplication([multiply, X, by, Y | T], Z) :-
|
||||||
|
simpoly(X*Y, A),
|
||||||
|
nlp_parse_multiplication([A|T], Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_multiplication([H|T], [H|Z]) :-
|
||||||
|
nlp_parse_multiplication(T, Z).
|
||||||
|
nlp_parse_multiplication([], []).
|
||||||
|
|
||||||
|
%% nlp_parse_sum(?List, ?List)
|
||||||
|
%
|
||||||
|
% Parse sums
|
||||||
|
%
|
||||||
|
nlp_parse_sum([X, plus, Y|T], Z) :-
|
||||||
|
simpoly(X+Y, A),
|
||||||
|
nlp_parse_sum([A|T], Z),
|
||||||
|
!.
|
||||||
|
nlp_parse_sum([H|T], [H|Z]) :-
|
||||||
|
nlp_parse_sum(T, Z).
|
||||||
|
nlp_parse_sum([], []).
|
||||||
|
|
||||||
|
%% list_of_atoms_to_list_of_strings(+List, -List) is det
|
||||||
|
%
|
||||||
|
% Converts a list of strings to a list of atoms
|
||||||
|
%
|
||||||
|
list_of_strings_to_list_of_atoms([H|T], [N|U]) :-
|
||||||
|
atom_string(N,H),
|
||||||
|
list_of_strings_to_list_of_atoms(T,U).
|
||||||
|
list_of_strings_to_list_of_atoms([],[]).
|
||||||
|
|
||||||
|
%% 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([]).
|
||||||
|
|
||||||
|
%% nlp_parse(+List, -List) is det
|
||||||
|
%
|
||||||
|
% Parses an instruction and returns the result
|
||||||
|
%
|
||||||
|
nlp_parse([], [void]).
|
||||||
|
nlp_parse(L, Z) :-
|
||||||
|
% Parsers are used in a priority basis
|
||||||
|
nlp_parse_numbers(L, A),
|
||||||
|
nlp_parse_power(A, B),
|
||||||
|
nlp_parse_multiplication(B, C),
|
||||||
|
nlp_parse_sum(C, Z).
|
||||||
|
|
||||||
|
%% nlp_handler(+L:List, -Z:String) is det
|
||||||
|
%
|
||||||
|
% Takes the user's request and returns the result in a pretty string
|
||||||
|
%
|
||||||
|
nlp_handler([''], void).
|
||||||
|
nlp_handler([show, stored, polynomials|L], Z) :-
|
||||||
|
findall(nm(X,Y), nlp_memory(X,Y),D),
|
||||||
|
nlp_print_memory(D),
|
||||||
|
!,
|
||||||
|
nlp_parse(L,[Z]).
|
||||||
|
nlp_handler([show|L], Z) :-
|
||||||
|
nlp_parse(L,[Z]).
|
||||||
|
nlp_handler([simplify|L], Z) :-
|
||||||
|
nlp_parse(L,[Z]).
|
||||||
|
nlp_handler(L, Z) :-
|
||||||
|
% Check if we really were able to compute the requested
|
||||||
|
nlp_parse(L, [Z]),
|
||||||
|
polynomial(Z).
|
||||||
|
|
||||||
/*******************************
|
/*******************************
|
||||||
* USER INTERFACE *
|
* USER INTERFACE *
|
||||||
*******************************/
|
*******************************/
|
||||||
|
|
||||||
|
%% polyplay() is det
|
||||||
|
%
|
||||||
|
% Interactive prompt for the NLP Interface
|
||||||
|
%
|
||||||
|
polyplay :-
|
||||||
|
write("> "),
|
||||||
|
read_string(user_input, "\n", "\r\t ", _, Stdin),
|
||||||
|
%string_lower(Stdin, Stdin_lower),
|
||||||
|
split_string(Stdin/*_lower*/, " ", "", LS),
|
||||||
|
list_of_strings_to_list_of_atoms(LS, R),
|
||||||
|
(
|
||||||
|
R == [bye],
|
||||||
|
write("See ya"),
|
||||||
|
!
|
||||||
|
;
|
||||||
|
(
|
||||||
|
nlp_handler(R, Z),
|
||||||
|
(
|
||||||
|
Z \== void,
|
||||||
|
writeln(Z)
|
||||||
|
;
|
||||||
|
!
|
||||||
|
)
|
||||||
|
;
|
||||||
|
writeln("I didn't understand what you want.")
|
||||||
|
),
|
||||||
|
polyplay
|
||||||
|
),
|
||||||
|
!.
|
||||||
|
|
||||||
/*
|
/*
|
||||||
poly2list/2 transforms a list representing a polynomial (second
|
poly2list/2 transforms a list representing a polynomial (second
|
||||||
argument) into a polynomial represented as an expression (first
|
argument) into a polynomial represented as an expression (first
|
||||||
@ -152,146 +330,6 @@ is_number_in_predicate(C, F) :-
|
|||||||
write(C),
|
write(C),
|
||||||
fail.
|
fail.
|
||||||
|
|
||||||
%% polyplay() is det
|
|
||||||
%
|
|
||||||
% Interactive prompt for the NLP Interface
|
|
||||||
%
|
|
||||||
polyplay :-
|
|
||||||
write("> "),
|
|
||||||
read_string(user_input, "\n", "\r\t ", _, Stdin),
|
|
||||||
string_lower(Stdin, Stdin_lower),
|
|
||||||
split_string(Stdin_lower, " ", "", LS),
|
|
||||||
list_of_strings_to_list_of_atoms(LS, R),
|
|
||||||
(
|
|
||||||
R == [bye],
|
|
||||||
write("See ya"),
|
|
||||||
!
|
|
||||||
;
|
|
||||||
(
|
|
||||||
nlp_handler(R, Z),
|
|
||||||
writeln(Z)
|
|
||||||
;
|
|
||||||
writeln("I didn't understand what you want.")
|
|
||||||
),
|
|
||||||
polyplay
|
|
||||||
),
|
|
||||||
!.
|
|
||||||
|
|
||||||
/*******************************
|
|
||||||
* NLP *
|
|
||||||
*******************************/
|
|
||||||
|
|
||||||
%% nlp_number(?W:Atom, ?D:Int) is det
|
|
||||||
%
|
|
||||||
% Definition of a Alphabetical and Numerical relation
|
|
||||||
%
|
|
||||||
nlp_number(zero, 0).
|
|
||||||
nlp_number(one, 1).
|
|
||||||
nlp_number(two, 2).
|
|
||||||
nlp_number(three, 3).
|
|
||||||
nlp_number(four, 4).
|
|
||||||
nlp_number(five, 5).
|
|
||||||
nlp_number(six, 6).
|
|
||||||
nlp_number(seven, 7).
|
|
||||||
nlp_number(eight, 8).
|
|
||||||
nlp_number(nine, 9).
|
|
||||||
nlp_number(ten, 10).
|
|
||||||
|
|
||||||
%% nlp_get_number_from_string(+X:String, -D:Int) is det
|
|
||||||
%
|
|
||||||
% Get number from string graciously
|
|
||||||
%
|
|
||||||
nlp_get_number_from_string(X, Z) :- nlp_number(X, Z), !.
|
|
||||||
nlp_get_number_from_string(X, X).
|
|
||||||
|
|
||||||
%% nlp_parse_numbers(?List, ?List) is det
|
|
||||||
%
|
|
||||||
% Parse numbers
|
|
||||||
%
|
|
||||||
nlp_parse_numbers([H|T], [N|U]) :- nlp_get_number_from_string(H, N), nlp_parse_numbers(T, U).
|
|
||||||
nlp_parse_numbers([], []).
|
|
||||||
|
|
||||||
%% nlp_parse_power(?List, ?List) is det
|
|
||||||
%
|
|
||||||
% Parse powers
|
|
||||||
%
|
|
||||||
nlp_parse_power([X, raised, to, Y | T], [K|NewT]) :-
|
|
||||||
number(X),
|
|
||||||
number(Y),
|
|
||||||
K is X ** Y,
|
|
||||||
nlp_parse_power(T, NewT),
|
|
||||||
!.
|
|
||||||
nlp_parse_power([X, raised, to, Y | T], [X^Y|NewT]) :-
|
|
||||||
number(X),
|
|
||||||
nlp_parse_power(T, NewT),
|
|
||||||
!.
|
|
||||||
nlp_parse_power([X, raised, to, Y | T], Z) :-
|
|
||||||
poly2list(X^Y, K),
|
|
||||||
nlp_parse_power(T, NewT),
|
|
||||||
append(K, NewT, Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_power([X, squared | T], Z) :-
|
|
||||||
number(X),
|
|
||||||
A is X**2,
|
|
||||||
nlp_parse_power([A|T], Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_power([X, squared | T], [X^2|Z]) :-
|
|
||||||
nlp_parse_power(T, Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_power([H|T], [H|Z]) :-
|
|
||||||
nlp_parse_power(T, Z).
|
|
||||||
nlp_parse_power([], []).
|
|
||||||
|
|
||||||
%% nlp_parse_multiplication(?List, ?List) is det
|
|
||||||
%
|
|
||||||
% Parse multiplication
|
|
||||||
%
|
|
||||||
nlp_parse_multiplication([X, times, Y | T], Z) :-
|
|
||||||
simpoly(X*Y, A),
|
|
||||||
nlp_parse_multiplication([A|T], Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_multiplication([multiply, X, by, Y | T], Z) :-
|
|
||||||
simpoly(X*Y, A),
|
|
||||||
nlp_parse_multiplication([A|T], Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_multiplication([H|T], [H|Z]) :-
|
|
||||||
nlp_parse_multiplication(T, Z).
|
|
||||||
nlp_parse_multiplication([], []).
|
|
||||||
|
|
||||||
%% nlp_parse_sum(?List, ?List)
|
|
||||||
%
|
|
||||||
% Parse sums
|
|
||||||
%
|
|
||||||
nlp_parse_sum([X, plus, Y|T], Z) :-
|
|
||||||
simpoly(X+Y, A),
|
|
||||||
nlp_parse_sum([A|T], Z),
|
|
||||||
!.
|
|
||||||
nlp_parse_sum([H|T], [H|Z]) :-
|
|
||||||
nlp_parse_sum(T, Z).
|
|
||||||
nlp_parse_sum([], []).
|
|
||||||
|
|
||||||
%% list_of_atoms_to_list_of_strings(+List, -List) is det
|
|
||||||
%
|
|
||||||
% Converts a list of strings to a list of atoms
|
|
||||||
%
|
|
||||||
list_of_strings_to_list_of_atoms([H|T], [N|U]) :- string_to_atom(H,N), list_of_strings_to_list_of_atoms(T,U).
|
|
||||||
list_of_strings_to_list_of_atoms([],[]).
|
|
||||||
|
|
||||||
%polynomial_variable_from_string(A, B) :- polynomial_variable(B),string_to_atom(A,B).
|
|
||||||
%nlp_parse_poly_vars([H|T], [N|U]) :- (polynomial_variable_from_string(H, N);H=N), nlp_parse_poly_vars(T, U),!.
|
|
||||||
%nlp_parse_poly_vars([], []).
|
|
||||||
|
|
||||||
nlp_parse(L, Z) :- nlp_parse_numbers(L, A), nlp_parse_power(A, B), nlp_parse_multiplication(B, C), nlp_parse_sum(C, Z).
|
|
||||||
|
|
||||||
%% nlp_handler(+L:List, -Z:String) is det
|
|
||||||
%
|
|
||||||
% Takes the user's request and returns the result in a pretty string.
|
|
||||||
%
|
|
||||||
nlp_handler([simplify|L], Z) :-
|
|
||||||
nlp_parse(L,[Z]).
|
|
||||||
nlp_handler(L, Z) :-
|
|
||||||
nlp_parse(L, [Z]).
|
|
||||||
|
|
||||||
/*******************************
|
/*******************************
|
||||||
* BACKEND *
|
* BACKEND *
|
||||||
*******************************/
|
*******************************/
|
||||||
|
Reference in New Issue
Block a user