This commit is contained in:
Vitor Santos Costa 2018-07-09 01:57:13 +01:00
parent ba00e98ad8
commit 064b84895e
3 changed files with 75 additions and 64 deletions

View File

@ -20,14 +20,15 @@
:- use_module(library(python)).
:- use_module(library(yapi)).
:- use_module(library(complete)).
:- use_module(library(verify)).
:- python_import(sys).
jupyter_query(Caller, Prog, Query ) :-
catch(
jupyter_cell(Caller, Prog, Query),
E,
'$Error'(E, top)
error(L,E),
system_error(L,E)
).
jupyter_cell(_Caller, Cell, _Line) :-
@ -41,17 +42,6 @@ jupyter_cell( Self, _, Line ) :-
%Self := Caller.query,
python_query(Self,Line).
restreams(call) :-
streams(true).
restreams(fail) :-
streams(false).
restreams(answer).
restreams(exit) :-
streams(false).
restreams(!).
restreams(external_exception(_)).
restreams(exception).
jupyter_consult(Text) :-
blank( Text ),
!.
@ -71,63 +61,17 @@ jupyter_consult(Cell) :-
maplist( code_type(space), L).
streams(false) :-
nb_setval(jupyter_cell, false),
close(user_input),
close(user_output),
close(user_error).
streams(false) :-
nb_setval(jupyter_cell, false),
close(user_input),
close(user_output),
close(user_error).
streams(true) :-
nb_setval(jupyter_cell, true),
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, Cell, P, Q ) :-
catch(
all_clear(Self, Cell, P, Q)
E,
system_error(error,E).
all_clear( Self, _Cell, P, Q) :-
no_errors( Self, P ),
yap_flag(singleton_variables, Old, false)
no_errors( Self, Q ).
no_errors( _Self, Text ) :-
blank(Text),
no_errors( Self, Text ) :-
setup_call_cleanup(
open_esh( Self, Text, Stream),
esh(Self, Stream),
close_esh( Self, Stream )
).
esh(Self, Stream) :-
repeat,
catch(
read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ),
Error,
syntax(Self, Error)
),
Cl == end_of_file,
!.
syntax(_Self, E) :- writeln(user_error, E), fail.
syntax(Self, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
Self.errors := [t(Cause,LN,CharPos,Details)] + Self.errors,
!.
syntax(_Self, E) :- throw(E).
open_esh(Self, Text, Stream) :-
Self.errors := [],
open_mem_read_stream( Text, Stream ).
:- initialization( nb_setval( jupyter, off ) ).
close_esh( _Self, Stream ) :-
close(Stream).
:- if( current_prolog_flag(apple, true) ).
:- putenv( 'LC_ALL', 'en_us:UTF-8').

View File

@ -0,0 +1,66 @@
/**
* @file jupyter.yap4py
*
* @brief JUpyter support.
*/
% :- module( verify,
% [all_clear/4,
% errors/2,
% ready/2,
s % completion/2,
% ]
%% ).
:- use_module(library(hacks)).
:- use_module(library(lists)).
:- use_module(library(maplist)).
:- use_module(library(python)).
:- use_module(library(yapi)).
:- python_import(sys).
all_clear( Self, _Cell, P, Q) :-
no_errors( Self, P ),
yap_flag(singleton_variables, Old, false),
no_errors( Self, Q ),
yap_flag(singleton_variables, _, Old).
no_errors( _Self, Text ) :-
blank(Text).
no_errors( Self, Text ) :-
setup_call_cleanup(
open_esh( Self, Text, Stream),
esh(Self, Stream),
close_esh( Self, Stream )
).
syntax(_Self, E) :- writeln(user_error, E), fail.
syntax(Self, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
Self.errors := [t(Cause,LN,CharPos,Details)] + Self.errors,
!.
syntax(_Self, E) :- throw(E).
open_esh(Self, Text, Stream) :-
Self.errors := [],
open_mem_read_stream( Text, Stream ).
esh(Self, Stream) :-
repeat,
catch(
read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ),
Error,
syntax(Self, Error)
),
Cl == end_of_file,
!,
V := Self.errors,
V == [].
close_esh( _Self, Stream ) :-
close(Stream).