2019-03-26 09:40:54 +00:00
|
|
|
|
2018-06-03 23:59:17 +01:00
|
|
|
/**
|
2019-02-13 09:44:24 +00:00
|
|
|
* @file jupyter.yap
|
2018-05-28 09:31:59 +01:00
|
|
|
*
|
|
|
|
* @brief JUpyter support.
|
|
|
|
*/
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
%:- yap_flag(gc_trace,verbose).
|
2019-03-27 16:31:31 +00:00
|
|
|
%% :- module( jupyter,
|
|
|
|
%% [jupyter_query/3,
|
|
|
|
%% jupyter_query/4,
|
|
|
|
%% op(100,fy,('$')),
|
|
|
|
%% op(950,fy,:=),
|
|
|
|
%% op(950,yfx,:=),
|
|
|
|
%% % op(950,fx,<-),
|
|
|
|
%% % op(950,yfx,<-),
|
|
|
|
%% op(50, yf, []),
|
|
|
|
%% op(50, yf, '()'),
|
|
|
|
%% op(100, xfy, '.'),
|
|
|
|
%% op(100, fy, '.'),
|
|
|
|
%% blank/1,
|
|
|
|
%% streams/1
|
|
|
|
%% ]
|
|
|
|
%% ).
|
2019-02-27 04:23:21 +00:00
|
|
|
|
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
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
|
|
|
|
:- use_module(library(python)).
|
2019-03-19 18:42:17 +00:00
|
|
|
:- use_module(library(yapi)).
|
2019-02-27 04:23:21 +00:00
|
|
|
:- use_module(library(complete)).
|
|
|
|
:- use_module(library(verify)).
|
2018-07-21 01:56:48 +01:00
|
|
|
|
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
|
|
|
|
2019-03-27 16:31:31 +00:00
|
|
|
%:- meta_predicate jupyter_query(+,:,+,-), jupyter_query(+,:,+).
|
2019-03-21 09:02:43 +00:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
jupyter_query(Caller, Cell, Line, Bindings ) :-
|
2019-03-27 16:31:31 +00:00
|
|
|
jupyter_cell(Caller, Cell, Line, Bindings).
|
2018-12-21 20:57:53 +00:00
|
|
|
|
2018-03-02 21:18:24 +00:00
|
|
|
jupyter_query(Caller, Cell, Line ) :-
|
2019-02-27 04:23:21 +00:00
|
|
|
jupyter_query( Caller, Cell, Line, _Bindings ).
|
|
|
|
|
|
|
|
next_streams( _Caller, exit, _Bindings ) :-
|
|
|
|
% Caller.answer := Bindings,
|
|
|
|
!.
|
|
|
|
next_streams( _Caller, answer, _Bindings ) :-
|
|
|
|
% Caller.answer := Bindings,
|
|
|
|
!.
|
|
|
|
next_streams(_, redo, _ ) :-
|
|
|
|
!.
|
2019-03-27 16:31:31 +00:00
|
|
|
next_streams( _, _, _ ). % :-
|
|
|
|
% streams(false).
|
2019-02-27 04:23:21 +00:00
|
|
|
|
|
|
|
|
2017-12-14 18:40:22 +00:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
jupyter_cell(_Caller, Cell, _Line, _) :-
|
|
|
|
jupyter_consult(Cell), %stack_dump,
|
2017-12-14 18:40:22 +00:00
|
|
|
fail.
|
2019-02-27 04:23:21 +00:00
|
|
|
jupyter_cell( _Caller, _, ¨¨ , _) :- !.
|
|
|
|
jupyter_cell( _Caller, _, Line , _) :-
|
2017-12-20 00:29:15 +00:00
|
|
|
blank( Line ),
|
|
|
|
!.
|
2019-02-27 04:23:21 +00:00
|
|
|
jupyter_cell(Caller, _, Line, Bindings ) :-
|
2018-12-11 12:50:52 +00:00
|
|
|
Query = Caller,
|
2018-07-10 23:21:19 +01:00
|
|
|
catch(
|
2019-03-26 09:40:54 +00:00
|
|
|
python_query(Query,Line, Bindings),
|
2018-10-15 23:59:08 +01:00
|
|
|
error(A,B),
|
2018-12-21 20:57:53 +00:00
|
|
|
system_error(A,B)
|
2018-07-10 23:21:19 +01:00
|
|
|
).
|
2018-06-01 08:37:25 +01:00
|
|
|
|
2018-06-01 13:22:13 +01:00
|
|
|
restreams(call) :-
|
2018-06-01 08:37:25 +01:00
|
|
|
streams(true).
|
|
|
|
restreams(fail) :-
|
|
|
|
streams(false).
|
2018-06-01 13:22:13 +01:00
|
|
|
restreams(answer).
|
2018-06-01 08:37:25 +01:00
|
|
|
restreams(exit) :-
|
|
|
|
streams(false).
|
2018-06-01 13:22:13 +01:00
|
|
|
restreams(!).
|
|
|
|
restreams(external_exception(_)).
|
|
|
|
restreams(exception).
|
2017-08-21 12:36:48 +01:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
%:- meta_predicate
|
|
|
|
|
2017-12-20 00:29:15 +00:00
|
|
|
jupyter_consult(Text) :-
|
|
|
|
blank( Text ),
|
|
|
|
!.
|
|
|
|
jupyter_consult(Cell) :-
|
2018-03-12 15:11:59 +00:00
|
|
|
% Name = 'Inp',
|
|
|
|
% stream_property(Stream, file_name(Name) ),
|
2018-06-05 11:20:39 +01:00
|
|
|
% setup_call_cleanup(
|
2018-07-10 23:21:19 +01:00
|
|
|
catch(
|
|
|
|
(
|
|
|
|
Options = [],
|
|
|
|
open_mem_read_stream( Cell, Stream),
|
2019-03-26 09:40:54 +00:00
|
|
|
load_files(user:Stream,[stream(Stream)| Options])
|
2018-07-10 23:21:19 +01:00
|
|
|
),
|
2018-10-15 23:59:08 +01:00
|
|
|
error(A,B),
|
2019-03-27 16:31:31 +00:00
|
|
|
system_error(A,B)
|
2018-07-10 23:21:19 +01:00
|
|
|
),
|
|
|
|
fail.
|
|
|
|
jupyter_consult(_Cell).
|
2017-12-20 00:29:15 +00:00
|
|
|
|
|
|
|
blank(Text) :-
|
2018-07-10 23:21:19 +01:00
|
|
|
atom(Text),
|
|
|
|
!,
|
2017-12-20 00:29:15 +00:00
|
|
|
atom_codes(Text, L),
|
2018-06-05 11:20:39 +01:00
|
|
|
maplist( code_type(space), L).
|
2018-07-10 23:21:19 +01:00
|
|
|
blank(Text) :-
|
|
|
|
string(Text),
|
|
|
|
!,
|
|
|
|
string_codes(Text, L),
|
|
|
|
maplist( code_type(space), L).
|
2018-03-12 15:11:59 +00:00
|
|
|
|
2018-07-21 01:56:48 +01:00
|
|
|
|
2019-02-27 04:23:21 +00:00
|
|
|
streams(false) :-
|
2019-03-26 09:40:54 +00:00
|
|
|
close(user_input),
|
2018-07-09 01:57:13 +01:00
|
|
|
close(user_output),
|
|
|
|
close(user_error).
|
2018-10-16 14:33:16 +01:00
|
|
|
streams( true) :-
|
2018-12-11 12:50:52 +00:00
|
|
|
open('/python/input', read, _Input, [alias(user_input),bom(false),script(false)]),
|
2018-07-27 11:11:04 +01:00
|
|
|
open('/python/sys.stdout', append, _Output, [alias(user_output)]),
|
|
|
|
open('/python/sys.stderr', append, _Error, [alias(user_error)]).
|
2017-08-21 12:36:48 +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-07-21 01:56:48 +01:00
|
|
|
%y:- ( start_low_level_trace ).
|