2017-12-20 00:29:15 +00:00
|
|
|
/**
|
|
|
|
* @file jupyter.yap
|
|
|
|
*
|
|
|
|
* @brief allow interaction between Jupyter and YAP.
|
|
|
|
*
|
|
|
|
* @long The code in here:
|
|
|
|
* - establishes communication between Prolog and Python Streams
|
|
|
|
* - inputs Prolog code and queries
|
|
|
|
* - supports completion of Prolog programs.
|
|
|
|
* -
|
|
|
|
*/
|
2017-08-21 12:36:48 +01:00
|
|
|
:- use_module(library(yapi)).
|
2017-08-27 22:27:51 +01:00
|
|
|
:- use_module(library(lists)).
|
|
|
|
:- use_module(library(maplist)).
|
2017-08-21 12:36:48 +01:00
|
|
|
:- use_module(library(python)).
|
|
|
|
|
|
|
|
:- python_import(sys).
|
|
|
|
|
2017-12-14 18:40:22 +00:00
|
|
|
user:jupyter_query(Self, Cell, Line ) :-
|
2017-08-21 12:36:48 +01:00
|
|
|
setup_call_cleanup(
|
|
|
|
enter_cell(Self),
|
2017-12-14 18:40:22 +00:00
|
|
|
jupyter_cell(Self, Cell, Line),
|
2017-12-20 00:29:15 +00:00
|
|
|
exit_cell(Self)
|
|
|
|
).
|
2017-12-14 18:40:22 +00:00
|
|
|
|
|
|
|
jupyter_cell(_Self, Cell, _) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
stop_low_level_trace,
|
|
|
|
jupyter_consult(Cell),
|
2017-12-14 18:40:22 +00:00
|
|
|
fail.
|
2017-12-20 00:29:15 +00:00
|
|
|
jupyter_cell( _Self, _, Line ) :-
|
|
|
|
blank( Line ),
|
|
|
|
!.
|
2017-12-14 18:40:22 +00:00
|
|
|
jupyter_cell( Self, _, Line ) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
start_low_level_trace,
|
2017-12-14 18:40:22 +00:00
|
|
|
python_query( Self, Line ).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2017-12-20 00:29:15 +00:00
|
|
|
jupyter_consult(Text) :-
|
|
|
|
blank( Text ),
|
|
|
|
!.
|
|
|
|
jupyter_consult(Cell) :-
|
|
|
|
open_mem_read_stream( Cell, Stream),
|
|
|
|
load_files(user:'jupyter cell',[stream(Stream)]).
|
|
|
|
%should load_files close?
|
|
|
|
|
|
|
|
blank(Text) :-
|
|
|
|
atom_codes(Text, L),
|
|
|
|
maplist( blankc, L).
|
|
|
|
|
|
|
|
blankc(' ').
|
|
|
|
blankc('\n').
|
|
|
|
blankc('\t').
|
|
|
|
|
2017-08-21 12:36:48 +01:00
|
|
|
enter_cell(_Self) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
%open('//python/sys.stdin', read, _Input, []),
|
2017-12-14 18:40:22 +00:00
|
|
|
open('//python/sys.stdout', append, _Output, []),
|
|
|
|
open('//python/sys.stdout', append, _Error, []),
|
2017-12-20 00:29:15 +00:00
|
|
|
%set_prolog_flag(user_input, _Input),
|
2017-12-13 16:56:10 +00:00
|
|
|
set_prolog_flag(user_output, _Output),
|
2017-12-20 00:29:15 +00:00
|
|
|
set_prolog_flag(user_error, _Error).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
|
|
|
exit_cell(_Self) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
%close( user_input),
|
2017-12-13 16:56:10 +00:00
|
|
|
close( user_output),
|
|
|
|
close( user_error).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
|
|
|
|
|
|
|
completions(S, Self) :-
|
2017-08-27 22:27:51 +01:00
|
|
|
open_mem_read_stream(S, St),
|
2017-08-21 12:36:48 +01:00
|
|
|
scan_to_list(St, Tokens),
|
2017-08-27 22:27:51 +01:00
|
|
|
close(St),
|
2017-08-21 12:36:48 +01:00
|
|
|
reverse(Tokens, RTokens),
|
2017-08-27 22:27:51 +01:00
|
|
|
strip_final_tokens(RTokens, MyTokens),
|
|
|
|
setof( Completion, complete(MyTokens, Completion), Cs),
|
2017-08-21 12:36:48 +01:00
|
|
|
Self.completions := Cs.
|
|
|
|
|
2017-08-27 22:27:51 +01:00
|
|
|
|
|
|
|
strip_final_tokens(['EOT'|Ts], Ts) :- !.
|
2017-11-13 11:02:35 +00:00
|
|
|
strip_final_tokens( Ts, Ts ).
|
|
|
|
|
2017-09-06 01:09:46 +01:00
|
|
|
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),
|
2017-08-21 12:36:48 +01:00
|
|
|
\+ arg( Rest ),
|
2017-09-06 01:09:46 +01:00
|
|
|
file_or_library( Prefix, C).
|
|
|
|
complete([C,l,-,'['|More],
|
|
|
|
isconsult(A),
|
|
|
|
%B = l,
|
|
|
|
C=atom(Prefix),
|
2017-08-21 12:36:48 +01:00
|
|
|
\+ arg( Rest ),
|
2017-09-06 01:09:46 +01:00
|
|
|
file_or_library( Prefix, C).
|
2017-08-21 12:36:48 +01:00
|
|
|
complete( [atom(F)|Rest], C) :-
|
|
|
|
\+ arg( Rest ),
|
|
|
|
predicate( F, Pred, Arity ),
|
2017-08-27 22:27:51 +01:00
|
|
|
cont( Arity, F, Pred, C).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2017-09-06 01:09:46 +01:00
|
|
|
isconsult( atom(use_module) ).
|
|
|
|
isconsult( atom(ensure_loaded) ).
|
|
|
|
isconsult( atom(compile) ).
|
|
|
|
isconsult( atom(consult) ).
|
|
|
|
isconsult( atom(reconsult) ).
|
|
|
|
isconsult( atom(load_files) ).
|
|
|
|
isconsult( '[' ).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2017-08-27 22:27:51 +01:00
|
|
|
arg([']'|_]).
|
|
|
|
arg([l|_]).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2017-11-13 11:02:35 +00:00
|
|
|
file_or_library(F,C) :-
|
2017-09-06 01:09:46 +01:00
|
|
|
libsym(C0),
|
2017-12-13 16:56:10 +00:00
|
|
|
atom_cooncat(F,C,C0).
|
2017-11-13 11:02:35 +00:00
|
|
|
file_or_library(F,C) :-
|
2017-12-13 16:56:10 +00:00
|
|
|
check_file(F,C).
|
|
|
|
|
2017-09-06 01:09:46 +01:00
|
|
|
check_file(F0,C) :-
|
|
|
|
atom_concat('\'',F,F0),
|
|
|
|
!,
|
|
|
|
absolute_file_name( F, FF, [access(none)] ),
|
2017-12-13 16:56:10 +00:00
|
|
|
atom_concat( FF, '*' , Pat),
|
2017-09-06 01:09:46 +01:00
|
|
|
absolute_file_name( Pat, C0, [glob(true)] ),
|
|
|
|
atom_concat(Pat,C00,C0),
|
|
|
|
atom_conct(C00,'\'',C).
|
|
|
|
check_file(F0,C) :-
|
2017-12-13 16:56:10 +00:00
|
|
|
atom_concat( F0, '*' , Pat),
|
2017-08-21 12:36:48 +01:00
|
|
|
absolute_file_name( Pat, C0, [glob(true)] ),
|
2017-09-06 01:09:46 +01:00
|
|
|
atom_concat(Pat,C,C0).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
|
|
|
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).
|
|
|
|
|
2017-12-13 16:56:10 +00:00
|
|
|
cont(0, F, P, P0) :-
|
2017-11-13 11:02:35 +00:00
|
|
|
atom_concat( F, P, P0 ).
|
2017-08-27 22:27:51 +01:00
|
|
|
cont( _, F, P, PB ):-
|
|
|
|
atom_concat( [F, P, '('], PB ).
|