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

70 lines
1.4 KiB
Plaintext
Raw Normal View History

2017-08-21 12:36:48 +01:00
%% @file yapi.yap
2017-05-08 19:04:16 +01:00
%% @brief support yap shell
%%
2017-08-21 12:36:48 +01:00
% :- yap_flag(verbose, verbose).
:- use_module( library(python) ).
:- module(yapi, [
2017-05-27 22:54:00 +01:00
python_ouput/0,
2017-06-05 13:06:12 +01:00
show_answer/2,
show_answer/3,
yap_query/4,
2017-08-21 12:36:48 +01:00
python_query/2,
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-08-21 12:36:48 +01:00
:- python_import(yap4py.yapi).
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-08-21 12:36:48 +01:00
:- initialization set_preds.
2017-05-27 22:54:00 +01:00
2017-08-21 12:36:48 +01:00
set_preds :-
current_predicate(P, Q),
functor(Q,P,A),
atom_string(P,S),
:= yap4py.yapi.named( S, A),
fail.
set_preds :-
system_predicate(P/A),
atom_string(P,S),
:= yap4py.yapi.named( S, A),
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
2017-08-21 12:36:48 +01:00
python_query( Self, String ) :-
yap_flag(typein_module, Mod),
atomic_to_term( String, Goal, VarNames ),
query_to_answer( Mod:Goal, VarNames, Status, Bindings),
maplist(in_dict(Self.bindings), Bindings),
write_query_answer( Bindings ),
nl( user_error ),
Self.port := Status.
in_dict(Dict, var([V0,V|Vs])) :- !,
Dict[V] := V0,
in_dict( Dict, var([V0|Vs])).
in_dict(Dict, nonvar([V0|Vs],G)) :- !,
Dict[V0] := G,
in_dict( Dict, var([V0|Vs])).
in_dict(_, _).