2017-05-08 19:04:16 +01:00
|
|
|
%% @file yapi.yap
|
|
|
|
%% @brief support yap shell
|
|
|
|
%%
|
2017-05-27 22:54:00 +01:00
|
|
|
:- module(yapi, [python_query/2,
|
|
|
|
python_ouput/0,
|
2017-06-05 13:06:12 +01:00
|
|
|
show_answer/2,
|
|
|
|
show_answer/3,
|
|
|
|
yap_query/4,
|
|
|
|
yapi_query/2]).
|
2017-05-08 19:04:16 +01:00
|
|
|
|
2017-05-19 09:56:37 +01:00
|
|
|
:- use_module( library(lists) ).
|
2017-05-08 19:04:16 +01:00
|
|
|
:- use_module( library(maplist) ).
|
|
|
|
:- use_module( library(rbtrees) ).
|
2017-06-05 13:06:12 +01:00
|
|
|
:- use_module( library(terms) ).
|
2017-06-06 12:47:59 +01:00
|
|
|
:- use_module( library(python) ).
|
2017-05-08 19:04:16 +01:00
|
|
|
|
|
|
|
|
2017-06-06 12:47:59 +01:00
|
|
|
%% @pred yap_query(sGoal, + VarList, +OutStream, - Dictionary)
|
2017-05-27 22:54:00 +01:00
|
|
|
%% @pred yap_query(0:Goal, + VarList, - Dictionary)
|
|
|
|
%%
|
|
|
|
%% dictionary, Examples
|
|
|
|
%%
|
|
|
|
%%
|
2017-06-06 12:47:59 +01:00
|
|
|
python_query( String, D ) :-
|
2017-06-05 13:06:12 +01:00
|
|
|
atomic_to_term( String, Goal, VarNames ),
|
2017-06-06 12:47:59 +01:00
|
|
|
yap_query( Goal, VarNames, user_error, Dict),
|
|
|
|
D := Dict,
|
|
|
|
yap4py.yapi.bindings := Dict.
|
2017-06-05 13:06:12 +01:00
|
|
|
|
|
|
|
%% @pred yapi_query( + VarList, - Dictionary)
|
|
|
|
%%
|
|
|
|
%% dictionary, Examples
|
|
|
|
%%
|
|
|
|
%%
|
2017-06-06 12:47:59 +01:00
|
|
|
yapi_query( VarNames, Dict ) :-
|
2017-06-05 13:06:12 +01:00
|
|
|
show_answer(VarNames, Dict).
|
|
|
|
|
|
|
|
|
2017-05-27 22:54:00 +01:00
|
|
|
|
2017-05-19 09:56:37 +01:00
|
|
|
%% @pred yap_query(0:Goal, + VarList, +OutStream, - Dictionary)
|
|
|
|
%% @pred yap_query(0:Goal, + VarList, - Dictionary)
|
|
|
|
%%
|
|
|
|
%% dictionary, Examples
|
|
|
|
%%
|
|
|
|
%%
|
|
|
|
yap_query( Goal, VarNames, Stream, Dictionary) :-
|
|
|
|
(
|
2017-06-06 12:47:59 +01:00
|
|
|
call(Goal)
|
2017-05-19 09:56:37 +01:00
|
|
|
*->
|
2017-06-06 12:47:59 +01:00
|
|
|
!,
|
|
|
|
show_answer(VarNames, Stream, Dictionary)
|
|
|
|
).
|
2017-05-19 09:56:37 +01:00
|
|
|
|
2017-06-06 12:47:59 +01:00
|
|
|
yap_query( VarNames, Dictionary) :-
|
2017-06-05 13:06:12 +01:00
|
|
|
yap_query( VarNames, user_output, Dictionary).
|
|
|
|
|
|
|
|
show_answer(QVs0, Dict) :-
|
2017-06-06 12:47:59 +01:00
|
|
|
show_answer(QVs0, user_error, Dict).
|
2017-05-08 19:04:16 +01:00
|
|
|
|
2017-06-06 12:47:59 +01:00
|
|
|
show_answer(QVs0, Stream, Dict) :-
|
2017-06-05 13:06:12 +01:00
|
|
|
copy_term(QVs0, QVs),
|
2017-06-06 12:47:59 +01:00
|
|
|
copy_term(QVs0, QVs1),
|
|
|
|
rb_new(RB),
|
|
|
|
foldl2(bind_qv, QVs, QVs1, [], LP, {}-RB, Dict-_),
|
2017-06-05 13:06:12 +01:00
|
|
|
!,
|
2017-06-06 12:47:59 +01:00
|
|
|
term_variables(QVs, IVs),
|
|
|
|
term_variables(QVs1, IVs1),
|
|
|
|
foldl( enumerate, IVs, IVs1, 1, _ ),
|
|
|
|
out(LP, Stream ).
|
2017-06-05 13:06:12 +01:00
|
|
|
show_answer(_, _, {}) :-
|
2017-06-06 12:47:59 +01:00
|
|
|
format(' yes.~n', [] ).
|
|
|
|
|
|
|
|
bind_qv(V=V0, V1 = V01, Vs, Vs, Vs1-RB, Vs1-RB) :-
|
|
|
|
var(V0),
|
|
|
|
!,
|
|
|
|
'$VAR'(V) = V0,
|
|
|
|
V1 = V01.
|
|
|
|
% atom_string(V1, V01).
|
|
|
|
bind_qv(V='$VAR'(Vi), V1=S1, Vs, [V='$VAR'(Vi)|Vs], D0-RB, D-RB) :- !,
|
|
|
|
add2dict(D0, V1:S1, D).
|
|
|
|
bind_qv(V=S, V1=S1, Vs, [V=S|Vs], D0-RB0, D-RB0) :-
|
|
|
|
% fix_tree( S, SS, S1, SS1, RB0, RBT),
|
|
|
|
add2dict(D0, V1:S1, D).
|
2017-05-19 09:56:37 +01:00
|
|
|
|
|
|
|
|
2017-06-06 12:47:59 +01:00
|
|
|
add2dict({}, B, {B}).
|
|
|
|
add2dict({C}, B, {B,C}).
|
|
|
|
|
|
|
|
enumerate('$VAR'(A), A, I, I1) :-
|
2017-05-19 09:56:37 +01:00
|
|
|
enum(I, Chars),
|
|
|
|
atom_codes(A,[0'_|Chars]),
|
|
|
|
I1 is I + 1.
|
|
|
|
|
|
|
|
enum(I, [C]) :-
|
|
|
|
I < 26,
|
2017-05-27 22:54:00 +01:00
|
|
|
!,
|
|
|
|
C is "A" + I.
|
2017-05-19 09:56:37 +01:00
|
|
|
enum(I, [C|Cs]) :-
|
|
|
|
J is I//26,
|
|
|
|
K is I mod 26,
|
|
|
|
C is "A" +K,
|
|
|
|
enum(J, Cs).
|
|
|
|
|
2017-06-06 12:47:59 +01:00
|
|
|
out(Bs, S) :-
|
2017-05-19 09:56:37 +01:00
|
|
|
output(Bs, S),
|
2017-06-06 12:47:59 +01:00
|
|
|
!.
|
|
|
|
out([_|Bs], S) :-
|
|
|
|
out(Bs, S).
|
2017-05-19 09:56:37 +01:00
|
|
|
|
|
|
|
output([V=B], S) :-
|
2017-05-27 22:54:00 +01:00
|
|
|
!,
|
|
|
|
format(S, '~a = ~q~n', [V, B]).
|
2017-06-06 12:47:59 +01:00
|
|
|
output([V=B|_Ns], S) :-
|
|
|
|
format( S, '~a = ~q.~n', [V, B]),
|
|
|
|
fail.
|
|
|
|
|
|
|
|
|
|
|
|
|