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-03-02 21:18:24 +00:00
|
|
|
%:- start_low_level_trace.
|
2018-02-26 21:38:19 +00:00
|
|
|
:- module(yapi, [
|
|
|
|
python_ouput/0,
|
|
|
|
show_answer/2,
|
|
|
|
show_answer/3,
|
|
|
|
yap_query/4,
|
|
|
|
python_query/2,
|
2018-05-27 00:47:03 +01:00
|
|
|
python_query/3,
|
2018-05-28 09:31:59 +01:00
|
|
|
python_import/1,
|
2018-02-26 21:38:19 +00:00
|
|
|
yapi_query/2
|
|
|
|
]).
|
2018-01-29 15:24:32 +00:00
|
|
|
|
2018-05-28 09:31:59 +01:00
|
|
|
:- yap_flag(verbose, silent).
|
2018-01-29 15:24:32 +00:00
|
|
|
|
2018-05-28 09:31:59 +01:00
|
|
|
:- use_module(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) ).
|
2018-05-28 09:31:59 +01:00
|
|
|
|
2018-02-08 10:48:02 +00:00
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
:- python_import(yap4py.yapi).
|
2018-03-19 11:43:14 +00:00
|
|
|
%:- python_import(gc).
|
|
|
|
|
|
|
|
:- meta_predicate( yapi_query(:,+) ).
|
2017-06-05 13:06:12 +01:00
|
|
|
|
2017-11-08 09:29:01 +00:00
|
|
|
%:- start_low_level_trace.
|
|
|
|
|
2017-06-05 13:06:12 +01:00
|
|
|
%% @pred yapi_query( + VarList, - Dictionary)
|
|
|
|
%%
|
|
|
|
%% dictionary, Examples
|
|
|
|
%%
|
|
|
|
%%
|
2017-08-21 12:36:48 +01:00
|
|
|
yapi_query( VarNames, Self ) :-
|
|
|
|
show_answer(VarNames, Dict),
|
|
|
|
Self.bindings := Dict.
|
2017-06-05 13:06:12 +01: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,
|
2017-08-21 12:36:48 +01:00
|
|
|
current_predicate(P, Q),
|
|
|
|
functor(Q,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 :-
|
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) :-
|
|
|
|
atomic_concat(`A`,I,N),
|
|
|
|
I1 is I+1.
|
2017-05-19 09:56:37 +01:00
|
|
|
|
2018-03-02 21:18:24 +00:00
|
|
|
python_query( Caller, String ) :-
|
2018-05-30 21:54:12 +01:00
|
|
|
atomic_to_term( String, Goal, VarNames ),
|
|
|
|
query_to_answer( Goal, VarNames, Status, Bindings),
|
|
|
|
atom_to_string( Status, SStatus ),
|
2018-05-31 00:15:48 +01:00
|
|
|
Caller.port := SStatus,
|
2017-08-21 12:36:48 +01:00
|
|
|
write_query_answer( Bindings ),
|
2017-12-20 00:29:15 +00:00
|
|
|
nl(user_error),
|
2018-05-31 00:15:48 +01:00
|
|
|
Caller.answer := {},
|
|
|
|
maplist(in_dict(Caller.answer), Bindings).
|
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
|
|
|
|
in_dict(Dict, var([V0,V|Vs])) :- !,
|
|
|
|
Dict[V] := V0,
|
|
|
|
in_dict( Dict, var([V0|Vs])).
|
2018-05-30 13:07:45 +01:00
|
|
|
in_dict(_Dict, var([_],_G)) :- !.
|
2017-08-21 12:36:48 +01:00
|
|
|
in_dict(Dict, nonvar([V0|Vs],G)) :- !,
|
|
|
|
Dict[V0] := G,
|
2018-05-31 00:15:48 +01:00
|
|
|
in_dict( Dict, nonvar(Vs, G) ).
|
2018-05-30 13:07:45 +01:00
|
|
|
in_dict(_Dict, nonvar([],_G)) :- !.
|
2018-06-01 08:37:25 +01:00
|
|
|
in_dict(_, _)
|