2018-06-03 23:59:17 +01:00
|
|
|
/**
|
2018-05-28 09:31:59 +01:00
|
|
|
* @file jupyter.yap4py
|
|
|
|
*
|
|
|
|
* @brief JUpyter support.
|
|
|
|
*/
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2018-07-10 23:21:19 +01:00
|
|
|
:- yap_flag(gc_trace,verbose).
|
2018-06-03 12:07:38 +01:00
|
|
|
|
2018-03-12 15:11:59 +00:00
|
|
|
% :- module( jupyter,
|
|
|
|
% [jupyter_query/3,
|
|
|
|
% errors/2,
|
|
|
|
% ready/2,
|
|
|
|
% completion/2,
|
|
|
|
% ]
|
|
|
|
%% ).
|
2018-05-28 09:31:59 +01:00
|
|
|
:- use_module(library(hacks)).
|
|
|
|
|
2018-01-18 14:47:27 +00:00
|
|
|
:- use_module(library(lists)).
|
|
|
|
:- use_module(library(maplist)).
|
2018-05-28 09:31:59 +01:00
|
|
|
|
2018-01-18 14:47:27 +00:00
|
|
|
:- use_module(library(python)).
|
2018-05-28 09:31:59 +01:00
|
|
|
:- use_module(library(yapi)).
|
2018-06-02 23:04:51 +01:00
|
|
|
:- use_module(library(complete)).
|
2018-01-05 16:57:38 +00:00
|
|
|
|
2018-01-18 14:47:27 +00:00
|
|
|
:- python_import(sys).
|
2018-01-05 16:57:38 +00:00
|
|
|
|
2018-07-10 23:21:19 +01:00
|
|
|
jupyter_query(Caller, Cell, Line ) :-
|
|
|
|
jupyter_cell(Caller, Cell, Line).
|
2017-12-14 18:40:22 +00:00
|
|
|
|
2018-06-05 11:20:39 +01:00
|
|
|
jupyter_cell(_Caller, Cell, _Line) :-
|
2018-03-12 15:11:59 +00:00
|
|
|
jupyter_consult(Cell), %stack_dump,
|
2017-12-14 18:40:22 +00:00
|
|
|
fail.
|
2018-06-05 11:20:39 +01:00
|
|
|
jupyter_cell( _Caller, _, '' ) :- !.
|
2018-03-02 21:18:24 +00:00
|
|
|
jupyter_cell( _Caller, _, Line ) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
blank( Line ),
|
|
|
|
!.
|
2018-07-10 23:21:19 +01:00
|
|
|
jupyter_cell( Caller, _, Line ) :-
|
|
|
|
Self := Caller.query,
|
|
|
|
catch(
|
|
|
|
python_query(Self,Line),
|
|
|
|
E=error(A,B),
|
|
|
|
system_error(A,B)
|
|
|
|
).
|
|
|
|
jupyter_cell(_,_,_).
|
|
|
|
|
|
|
|
restreams(call) :-
|
|
|
|
streams(true).
|
|
|
|
restreams(fail) :-
|
|
|
|
streams(false).
|
|
|
|
restreams(answer).
|
|
|
|
restreams(exit) :-
|
|
|
|
streams(false).
|
|
|
|
restreams(!).
|
|
|
|
restreams(external_exception(_)).
|
|
|
|
restreams(exception).
|
2018-06-01 08:37:25 +01:00
|
|
|
|
2017-12-20 00:29:15 +00:00
|
|
|
jupyter_consult(Text) :-
|
|
|
|
blank( Text ),
|
|
|
|
!.
|
|
|
|
jupyter_consult(Cell) :-
|
2018-07-10 23:21:19 +01:00
|
|
|
% Name = 'Inp',
|
|
|
|
% stream_property(Stream, file_name(Name) ),
|
|
|
|
% setup_call_cleanup(
|
|
|
|
catch(
|
|
|
|
(
|
|
|
|
Options = [],
|
|
|
|
open_mem_read_stream( Cell, Stream),
|
|
|
|
load_files(user:'jupyter cell',[stream(Stream)| Options])
|
|
|
|
),
|
|
|
|
E=error(A,B),
|
|
|
|
(close(Stream), system_error(A,B))
|
|
|
|
),
|
|
|
|
fail.
|
|
|
|
jupyter_consult(_Cell).
|
|
|
|
|
|
|
|
blank(Text) :-
|
|
|
|
atom(Text),
|
|
|
|
!,
|
|
|
|
atom_codes(Text, L),
|
|
|
|
maplist( code_type(space), L).
|
|
|
|
blank(Text) :-
|
|
|
|
string(Text),
|
|
|
|
!,
|
|
|
|
string_codes(Text, L),
|
|
|
|
maplist( code_type(space), L).
|
2018-07-09 00:50:00 +01:00
|
|
|
|
2018-07-09 01:57:13 +01:00
|
|
|
streams(false) :-
|
|
|
|
close(user_input),
|
|
|
|
close(user_output),
|
|
|
|
close(user_error).
|
2018-03-12 15:11:59 +00:00
|
|
|
streams(true) :-
|
2018-07-10 23:21:19 +01:00
|
|
|
open('/python/input', read, Input, [alias(user_input),bom(false),script(false)]),
|
|
|
|
open('/python/sys.stdout', append, Output, [alias(user_output)]),
|
|
|
|
open('/python/sys.stderr', append, Error, [alias(user_error)]).
|
|
|
|
|
|
|
|
ready(_Self, Line ) :-
|
|
|
|
blank( Line ),
|
|
|
|
!.
|
|
|
|
ready(Self, Line ) :-
|
|
|
|
errors( Self, Line ),
|
|
|
|
\+ syntax_error(_,_).
|
|
|
|
|
|
|
|
errors( Self, Text ) :-
|
|
|
|
setup_call_cleanup(
|
|
|
|
open_events( Self, Text, Stream),
|
|
|
|
goals(Self, Stream),
|
|
|
|
close_events( Self )
|
|
|
|
).
|
|
|
|
|
|
|
|
clauses(_Self, Stream) :-
|
|
|
|
repeat,
|
|
|
|
read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ),
|
|
|
|
% command( Self, Cl ),
|
|
|
|
Cl == end_of_file,
|
|
|
|
!.
|
|
|
|
|
|
|
|
goals(_Self, Stream) :-
|
|
|
|
repeat,
|
|
|
|
read_term(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ),
|
|
|
|
% command( Self, Cl ),
|
|
|
|
Cl == end_of_file,
|
|
|
|
!.
|
|
|
|
|
|
|
|
command(_, end_of_file) :- !.
|
|
|
|
|
|
|
|
command( _Self, ( :- op(Prio,Assoc,Name) ) ) :-
|
|
|
|
addop(Prio,Assoc,Name).
|
|
|
|
|
|
|
|
command( _Self, ( :- module(Name, Exports) )) :-
|
|
|
|
retract( active_module( M0 ) ),
|
|
|
|
atom_concat( '__m0_', Name, M ),
|
|
|
|
assert( active_module(M) ),
|
|
|
|
assert( undo( active_module(M0) ) ),
|
|
|
|
maplist( addop2(M), Exports).
|
|
|
|
|
|
|
|
|
|
|
|
addop(Prio,Assoc,Name) :-
|
|
|
|
(
|
|
|
|
current_op(OPrio, SimilarAssoc, Name),
|
|
|
|
op(Prio, Assoc, Name),
|
|
|
|
matched_op(Assoc, SimilarAssoc)
|
|
|
|
->
|
|
|
|
assertz( undo(op( OPrio, Assoc, Name ) ) )
|
|
|
|
;
|
|
|
|
assertz( undo(op( 0, Assoc, Name ) ) )
|
|
|
|
).
|
|
|
|
|
|
|
|
addop2(M, op(Prio, Assoc, Name)) :-
|
|
|
|
addop( Prio, Assoc, M:Name ).
|
|
|
|
|
|
|
|
matched_op(A, B) :-
|
|
|
|
optype( A, T),
|
|
|
|
optype( B, T).
|
|
|
|
|
|
|
|
optype(fx,pre).
|
|
|
|
optype(fy,pre).
|
|
|
|
optype(xfx,in).
|
|
|
|
optype(xfy,in).
|
|
|
|
optype(yfx,in).
|
|
|
|
optype(yfy,in).
|
|
|
|
optype(xf,pos).
|
|
|
|
optype(yf,pos).
|
|
|
|
|
|
|
|
:- dynamic user:portray_message/2.
|
|
|
|
:- multifile user:portray_message/2.
|
|
|
|
|
|
|
|
:- dynamic syntax_error/4, undo/1.
|
|
|
|
|
|
|
|
user:portray_message(_Severity, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
|
|
|
|
nb_getval(jupyter_cell, on),
|
|
|
|
assert( syntax_error(Cause,LN,CharPos,Details) ).
|
|
|
|
user:portray_message(_Severity, error(style_check(_),_) ) :-
|
|
|
|
nb_getval(jupyter_cell, on).
|
|
|
|
|
|
|
|
open_events(Self, Text, Stream) :-
|
|
|
|
Self.errors := [],
|
|
|
|
nb_setval( jupyter, on),
|
|
|
|
open_mem_read_stream( Text, Stream ).
|
|
|
|
|
|
|
|
:- initialization( nb_setval( jupyter, off ) ).
|
|
|
|
|
|
|
|
close_events( _Self ) :-
|
|
|
|
nb_setval( jupyter, off ),
|
|
|
|
retract( undo(G) ),
|
|
|
|
call(G),
|
|
|
|
fail.
|
|
|
|
close_events( Self ) :-
|
|
|
|
retract( syntax_error( C, L, N, A )),
|
|
|
|
Self.errors := [t(C,L,N,A)] + Self.errors,
|
|
|
|
fail.
|
|
|
|
close_events( _ ).
|
|
|
|
|
2018-07-09 00:50:00 +01:00
|
|
|
|
2018-05-21 14:45:24 +01:00
|
|
|
:- if( current_prolog_flag(apple, true) ).
|
|
|
|
|
|
|
|
:- putenv( 'LC_ALL', 'en_us:UTF-8').
|
|
|
|
|
|
|
|
plot_inline :-
|
|
|
|
X := self.inline_plotting,
|
|
|
|
nb_setval(inline, X ),
|
|
|
|
X = true,
|
|
|
|
!,
|
|
|
|
:= (
|
|
|
|
import( matplotlib ),
|
|
|
|
matplotlib.use( `nbagg` )
|
|
|
|
).
|
|
|
|
|
|
|
|
:- endif.
|
|
|
|
|
2018-03-02 21:18:24 +00:00
|
|
|
%:- ( start_low_level_trace ).
|