cmmake
This commit is contained in:
122
packages/python/swig/prolog/jupyter.yap
Normal file
122
packages/python/swig/prolog/jupyter.yap
Normal file
@@ -0,0 +1,122 @@
|
||||
|
||||
:- use_module(library(yapi)).
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(maplist)).
|
||||
:- use_module(library(python)).
|
||||
|
||||
:- python_import(sys).
|
||||
|
||||
jupyter_query(Self, Cell) :-
|
||||
setup_call_cleanup(
|
||||
enter_cell(Self),
|
||||
python_query(Self, Cell),
|
||||
exit_cell(Self)
|
||||
).
|
||||
|
||||
enter_cell(_Self) :-
|
||||
open('//python/sys.stdout', append, _Output, [alias(jupo)]),
|
||||
open('//python/sys.stdout', append, _, [alias(jupe)]),
|
||||
set_prolog_flag(user_output, jupo),
|
||||
set_prolog_flag(user_error, jupe).
|
||||
|
||||
exit_cell(_Self) :-
|
||||
close( jupo),
|
||||
close( jupe).
|
||||
|
||||
|
||||
completions(S, Self) :-
|
||||
open_mem_read_stream(S, St),
|
||||
scan_to_list(St, Tokens),
|
||||
close(St),
|
||||
reverse(Tokens, RTokens),
|
||||
strip_final_tokens(RTokens, MyTokens),
|
||||
setof( Completion, complete(MyTokens, Completion), Cs),
|
||||
Self.completions := Cs.
|
||||
|
||||
|
||||
strip_final_tokens(['EOT'|Ts], Ts) :- !.
|
||||
strip_final_tokens( Ts, Ts ).|_],
|
||||
complete([E,l,C,l,A|More],
|
||||
isconsult(A),
|
||||
%B = l,
|
||||
library(C,Lib),
|
||||
%D=l,
|
||||
E=atom(Prefix),
|
||||
\+ arg( Rest ),
|
||||
check_library( Prefix, Lib, C).
|
||||
complete([E,l,C,l,-,'['|More],
|
||||
isconsult(A),
|
||||
%B = l,
|
||||
library(C,Lib),
|
||||
%D=l,
|
||||
E=atom(Prefix),
|
||||
\+ arg( Rest ),
|
||||
check_library( Prefix, Lib, C).
|
||||
complete([C,l,A|More],
|
||||
isconsult(A),
|
||||
%B = l,
|
||||
C=atom(Prefix),
|
||||
\+ arg( Rest ),
|
||||
file_or_library( Prefix, C).
|
||||
complete([C,l,-,'['|More],
|
||||
isconsult(A),
|
||||
%B = l,
|
||||
C=atom(Prefix),
|
||||
\+ arg( Rest ),
|
||||
file_or_library( Prefix, C).
|
||||
complete( [atom(F)|Rest], C) :-
|
||||
\+ arg( Rest ),
|
||||
predicate( F, Pred, Arity ),
|
||||
cont( Arity, F, Pred, C).
|
||||
|
||||
isconsult( atom(use_module) ).
|
||||
isconsult( atom(ensure_loaded) ).
|
||||
isconsult( atom(compile) ).
|
||||
isconsult( atom(consult) ).
|
||||
isconsult( atom(reconsult) ).
|
||||
isconsult( atom(load_files) ).
|
||||
isconsult( '[' ).
|
||||
|
||||
arg([']'|_]).
|
||||
arg([l|_]).
|
||||
|
||||
fileerrors-or_library(F,C) :-
|
||||
libsym(C0),
|
||||
atom_cooncat(F,C,Co).
|
||||
fileerrors-or_library(F,C) :-
|
||||
check_file(F0,C).
|
||||
|
||||
check_file(F0,C) :-
|
||||
atom_concat('\'',F,F0),
|
||||
!,
|
||||
absolute_file_name( F, FF, [access(none)] ),
|
||||
atom_concat( F, '*' , Pat),
|
||||
absolute_file_name( Pat, C0, [glob(true)] ),
|
||||
atom_concat(Pat,C00,C0),
|
||||
atom_conct(C00,'\'',C).
|
||||
check_file(F0,C) :-
|
||||
atom_concat( F, '*' , Pat),
|
||||
absolute_file_name( Pat, C0, [glob(true)] ),
|
||||
atom_concat(Pat,C,C0).
|
||||
|
||||
check_library( Lib, F, C) :-
|
||||
atom_concat( F, '*' , Pat),
|
||||
LibF =.. [Lib(Pat)],
|
||||
absolute_file_name( LibF, Lib, [glob(true)] ),
|
||||
file_directory_name( Lib, Name),
|
||||
( atom_concat(C, '.yap', Name) -> true ;
|
||||
atom_concat(C, '.ypp', Name) -> true ;
|
||||
atom_concat(C, '.prolog', Name) -> true
|
||||
).
|
||||
|
||||
predicate(N,P,A) :-
|
||||
system_predicate(P0/A),
|
||||
atom_concat(N,P,P0).
|
||||
predicate(N,P,A) :-
|
||||
current_predicate(P0/A),
|
||||
atom_concat(N,P,P0).
|
||||
|
||||
cont(0, F, P, P0)- :-
|
||||
atom_concat( F, P, PB ).
|
||||
cont( _, F, P, PB ):-
|
||||
atom_concat( [F, P, '('], PB ).
|
69
packages/python/swig/prolog/yapi.yap
Normal file
69
packages/python/swig/prolog/yapi.yap
Normal file
@@ -0,0 +1,69 @@
|
||||
%% @file yapi.yap
|
||||
%% @brief support yap shell
|
||||
%%
|
||||
|
||||
% :- yap_flag(verbose, verbose).
|
||||
|
||||
:- use_module( library(python) ).
|
||||
|
||||
:- module(yapi, [
|
||||
python_ouput/0,
|
||||
show_answer/2,
|
||||
show_answer/3,
|
||||
yap_query/4,
|
||||
python_query/2,
|
||||
yapi_query/2
|
||||
]).
|
||||
|
||||
:- use_module( library(lists) ).
|
||||
:- use_module( library(maplist) ).
|
||||
:- use_module( library(rbtrees) ).
|
||||
:- use_module( library(terms) ).
|
||||
:- use_module( library(python) ).
|
||||
|
||||
:- python_import(yap4py.yapi).
|
||||
|
||||
%% @pred yapi_query( + VarList, - Dictionary)
|
||||
%%
|
||||
%% dictionary, Examples
|
||||
%%
|
||||
%%
|
||||
yapi_query( VarNames, Self ) :-
|
||||
show_answer(VarNames, Dict),
|
||||
Self.bindings := Dict.
|
||||
|
||||
:- initialization set_preds.
|
||||
|
||||
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.
|
||||
|
||||
argi(N,I,I1) :-
|
||||
atomic_concat(`A`,I,N),
|
||||
I1 is I+1.
|
||||
|
||||
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(_, _).
|
Reference in New Issue
Block a user