This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
yap-6.3/packages/python/swig/prolog/yapi.yap

120 lines
2.2 KiB
Plaintext
Raw Normal View History

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-07-21 01:56:48 +01: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
%% ]).
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-07-21 01:56:48 +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-12-21 20:57:53 +00:00
:- python_import(json).
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.
2018-12-21 20:57:53 +00:00
%% @pred yapi_query( + VarList, - Dictionary)
%%
%% dictionary, Examples
%%
%%
yapi_query( VarNames, Self ) :-
2017-08-21 12:36:48 +01:00
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),
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) :-
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 ),
2018-12-23 15:38:56 +00:00
query_to_answer( Goal, _, Status, VarNames, Bindings),
2018-07-23 17:13:51 +01:00
Caller.port := Status,
2018-12-23 15:38:56 +00:00
output(Caller, Bindings).
output( _, Bindings ) :-
write_query_answer( Bindings ),
fail.
output( Caller, Bindings ) :-
answer := {},
foldl(ground_dict(answer), Bindings, [], Ts),
term_variables( Ts, Hidden),
foldl(bv, Hidden , 0, _),
2018-12-21 20:57:53 +00:00
maplist(into_dict(answer),Ts),
Caller.answer := json.dumps(answer),
2018-12-23 15:38:56 +00:00
S := Caller.answer,
format(user_error, '~nor ~s~n~n',S),
fail.
output(_Caller, _Bindings).
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) :-
2018-12-23 15:38:56 +00:00
python_represents(D[V0], T).
2018-12-21 20:57:53 +00:00
2018-12-11 12:50:52 +00:00
/**
*
*/
2018-12-23 15:38:56 +00:00
ground_dict(_Dict,var([_V]), I, I) :-
!.
ground_dict(_Dict,var([V,V]), I, I) :-
2018-12-21 20:57:53 +00:00
!.
2018-12-23 15:38:56 +00:00
ground_dict(Dict, nonvar([V0|Vs],T),I0, [V0=T| I0]) :-
2018-12-21 20:57:53 +00:00
!,
2018-12-23 15:38:56 +00:00
ground_dict(Dict, var([V0|Vs]),I0, I0).
ground_dict(Dict, var([V0,V1|Vs]), I, I) :-
2018-12-21 20:57:53 +00:00
!,
2018-12-23 15:38:56 +00:00
Dict[V1] := V0,
ground_dict(Dict, var([V0|Vs]), I, I).
2018-12-21 20:57:53 +00:00
2018-12-11 08:16:54 +00:00