2018-03-19 11:43:14 +00:00
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
%% @file yapi.yap
|
2017-05-08 19:04:16 +01:00
|
|
|
%% @brief support yap shell
|
|
|
|
%%
|
2018-01-29 15:24:32 +00:00
|
|
|
|
2019-03-27 16:31:31 +00:00
|
|
|
%% :- module(yapi, [
|
|
|
|
%% python_ouput/0,
|
|
|
|
%% show_answer/2,
|
|
|
|
%% show_answer/3,
|
|
|
|
%% yap_query/4,
|
|
|
|
%% python_query/2,
|
|
|
|
%% python_query/3,
|
|
|
|
%% python_import/1,
|
|
|
|
%% yapi_query/2
|
|
|
|
%% ]).
|
2019-02-27 04:23:21 +00:00
|
|
|
|
|
|
|
%:- yap_flag(verbose, silent).
|
2018-01-29 15:24:32 +00:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
:- reexport(library(python)).
|
2018-01-29 15:24:32 +00: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) ).
|
2019-02-27 04:23:21 +00:00
|
|
|
|
2018-02-08 10:48:02 +00:00
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
:- python_import(yap4py.yapi).
|
2018-12-21 20:57:53 +00:00
|
|
|
:- python_import(json).
|
2018-03-19 11:43:14 +00:00
|
|
|
%:- python_import(gc).
|
|
|
|
|
2019-03-21 09:02:43 +00:00
|
|
|
:- meta_predicate yapi_query(:,+), python_query(+,:), python_query(+,:,-) .
|
2017-06-05 13:06:12 +01:00
|
|
|
|
2017-11-08 09:29:01 +00:00
|
|
|
%:- start_low_level_trace.
|
|
|
|
|
2018-12-21 20:57:53 +00:00
|
|
|
%% @pred yapi_query( + VarList, - Dictionary)
|
|
|
|
%%
|
|
|
|
%% dictionary, Examples
|
|
|
|
%%
|
|
|
|
%%
|
2019-03-26 09:40:54 +00:00
|
|
|
yapi_query( VarNames, Caller ) :-
|
2017-08-21 12:36:48 +01:00
|
|
|
show_answer(VarNames, Dict),
|
2019-03-26 09:40:54 +00:00
|
|
|
Caller.bindings := Dict.
|
2017-06-05 13:06:12 +01:00
|
|
|
|
2017-11-08 09:29:01 +00:00
|
|
|
|
2019-03-19 18:42:17 +00:00
|
|
|
|
|
|
|
|
2017-11-08 09:29:01 +00:00
|
|
|
%:- initialization set_preds.
|
2017-05-27 22:54:00 +01:00
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
set_preds :-
|
2018-03-12 15:11:59 +00:00
|
|
|
fail,
|
2018-12-21 20:57:53 +00:00
|
|
|
current_predicate(P, Q),
|
|
|
|
functor(Q,P,A),
|
2017-08-21 12:36:48 +01:00
|
|
|
atom_string(P,S),
|
2017-11-08 09:29:01 +00:00
|
|
|
catch(
|
|
|
|
:= yap4py.yapi.named( S, A),
|
|
|
|
_,
|
|
|
|
fail),
|
2017-08-21 12:36:48 +01:00
|
|
|
fail.
|
|
|
|
set_preds :-
|
2018-03-12 15:11:59 +00:00
|
|
|
fail,
|
2017-08-21 12:36:48 +01:00
|
|
|
system_predicate(P/A),
|
|
|
|
atom_string(P,S),
|
2017-11-08 09:29:01 +00:00
|
|
|
catch(
|
|
|
|
:= yap4py.yapi.named( S, A),
|
|
|
|
_,
|
|
|
|
fail),
|
2017-08-21 12:36:48 +01:00
|
|
|
fail.
|
|
|
|
set_preds.
|
2017-05-19 09:56:37 +01:00
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
argi(N,I,I1) :-
|
2019-02-27 04:23:21 +00:00
|
|
|
atomic_concat('A',I,N),
|
2017-08-21 12:36:48 +01:00
|
|
|
I1 is I+1.
|
2017-05-19 09:56:37 +01:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
python_query( Caller, String ) :-
|
2019-03-19 18:42:17 +00:00
|
|
|
python_query( Caller, String, _Bindings).
|
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
python_query( Caller, String, Bindings ) :-
|
2018-05-30 21:54:12 +01:00
|
|
|
atomic_to_term( String, Goal, VarNames ),
|
2019-03-26 09:40:54 +00:00
|
|
|
query_to_answer( user:Goal, VarNames, Status, Bindings),
|
2019-03-19 18:42:17 +00:00
|
|
|
Caller.q.port := Status,
|
|
|
|
output(Caller, Bindings).
|
|
|
|
|
2019-03-20 10:52:38 +00:00
|
|
|
%% output( _, Bindings ) :-
|
|
|
|
%% write_query_answer( Bindings ),
|
|
|
|
%% fail.
|
2019-03-19 18:42:17 +00:00
|
|
|
output( Caller, Bindings) :-
|
2019-03-26 09:40:54 +00:00
|
|
|
copy_term( Bindings, Bs),
|
|
|
|
simplify(Bs, 1, Bss),
|
|
|
|
numbervars(Bss, 0, _),
|
|
|
|
maplist(into_dict(Caller),Bss).
|
|
|
|
|
|
|
|
simplify([],_,[]).
|
|
|
|
simplify([X=V|Xs], [X=V|NXs]) :-
|
|
|
|
var(V),
|
|
|
|
!,
|
|
|
|
X=V,
|
|
|
|
simplify(Xs,NXs).
|
|
|
|
simplify([X=V|Xs], I, NXs) :-
|
|
|
|
var(V),
|
|
|
|
!,
|
|
|
|
X=V,
|
|
|
|
simplify(Xs,I,NXs).
|
|
|
|
simplify([X=V|Xs], I, [X=V|NXs]) :-
|
|
|
|
!,
|
|
|
|
simplify(Xs,I,NXs).
|
|
|
|
simplify([G|Xs],I, [D=G|NXs]) :-
|
|
|
|
I1 is I+1,
|
|
|
|
atomic_concat(['__delay_',I,'__'],D),
|
|
|
|
simplify(Xs,I1,NXs).
|
|
|
|
|
2019-03-19 18:42:17 +00:00
|
|
|
|
2018-12-21 20:57:53 +00:00
|
|
|
bv(V,I,I1) :-
|
|
|
|
atomic_concat(['__',I],V),
|
|
|
|
I1 is I+1.
|
|
|
|
|
|
|
|
into_dict(D,V0=T) :-
|
2019-03-26 09:40:54 +00:00
|
|
|
listify(T,L),
|
|
|
|
D.q.answer[V0] := L.
|
|
|
|
|
|
|
|
listify('$VAR'(Bnd), V) :-
|
|
|
|
!,
|
|
|
|
listify_var(Bnd, V).
|
|
|
|
listify([A|As], V) :-
|
|
|
|
!,
|
|
|
|
maplist(listify,[A|As], V).
|
|
|
|
listify(A:As, A:Vs) :-
|
|
|
|
(atom(A);string(A)),
|
|
|
|
!,
|
|
|
|
maplist(listify,As, Vs).
|
|
|
|
listify(WellKnown, V) :-
|
|
|
|
WellKnown=..[N|As],
|
|
|
|
length(As,Sz),
|
|
|
|
well_known(N,Sz),
|
|
|
|
!,
|
|
|
|
maplist(listify,As, Vs),
|
|
|
|
V =.. [N|Vs].
|
|
|
|
|
|
|
|
listify('$VAR'(Bnd), V) :-
|
|
|
|
!,
|
|
|
|
listify_var(Bnd, V).
|
|
|
|
listify(T, t(S,V)) :-
|
|
|
|
T =.. [S,A|As],
|
|
|
|
!,
|
|
|
|
maplist(listify, [A|As], Vs),
|
|
|
|
V =.. [t|Vs].
|
|
|
|
listify(S, S).
|
|
|
|
|
|
|
|
listify_var(I, S) :-
|
|
|
|
I >= 0,
|
|
|
|
I =< 26,
|
|
|
|
!,
|
|
|
|
V is 0'A+I,
|
|
|
|
string_codes(S, [V]).
|
|
|
|
listify_var(I, S) :-
|
|
|
|
I < 0,
|
|
|
|
I >= -26,
|
|
|
|
!,
|
|
|
|
V is 0'A+I,
|
|
|
|
string_codes(S, [0'_+V]).
|
|
|
|
listify_var(S, S).
|
|
|
|
|
|
|
|
well_known(+,2).
|
|
|
|
well_known(-,2).
|
|
|
|
well_known(*,2).
|
|
|
|
well_known(/,2).
|
|
|
|
well_known((','),2).
|
2019-03-19 18:42:17 +00:00
|
|
|
|