error
This commit is contained in:
@@ -22,6 +22,7 @@ X_API PyObject *py_Atoms;
|
||||
X_API PyObject *py_Builtin;
|
||||
X_API PyObject *py_Yapex;
|
||||
X_API PyObject *py_Sys;
|
||||
X_API PyObject * pYAPError;
|
||||
PyObject *py_Context;
|
||||
PyObject *py_ModDict;
|
||||
|
||||
|
@@ -88,6 +88,7 @@ extensions = [Extension('_yap', native_sources,
|
||||
('MINOR_VERSION', '0'),
|
||||
('_YAP_NOT_INSTALLED_', '1'),
|
||||
('YAP_PYTHON', '1'),
|
||||
('PYTHONSWIG', '1'),
|
||||
('_GNU_SOURCE', '1')],
|
||||
runtime_library_dirs=[
|
||||
abspath(join(sysconfig.get_path('platlib'),'yap4py')), abspath(sysconfig.get_path('platlib')),'${CMAKE_INSTALL_FULL_LIBDIR}'],
|
||||
|
@@ -49,6 +49,7 @@ class JupyterEngine( Engine ):
|
||||
args = EngineArgs(**kwargs)
|
||||
args.jupyter = True
|
||||
Engine.__init__(self, args)
|
||||
self.errors = None
|
||||
self.goal(set_prolog_flag('verbose', 'silent'),True)
|
||||
self.goal(compile(library('jupyter')), True)
|
||||
self.goal(set_prolog_flag('verbose', 'normal'), True)
|
||||
|
@@ -95,7 +95,6 @@ set (PYTHON_SOURCES backcall.py yap_kernel_launcher.py docs/conf.py
|
||||
yap_ipython/lib/kernel.py yap_ipython/lib/latextools.py
|
||||
yap_ipython/lib/lexers.py yap_ipython/lib/pretty.py
|
||||
yap_ipython/lib/security.py yap_ipython/lib/tests
|
||||
yap_ipython/prolog/jupyter.yap
|
||||
yap_ipython/sphinxext/custom_doctests.py
|
||||
yap_ipython/sphinxext/__init__.py
|
||||
yap_ipython/sphinxext/ipython_console_highlighting.py
|
||||
|
@@ -6,13 +6,11 @@
|
||||
|
||||
:- yap_flag(gc_trace,verbose).
|
||||
|
||||
% :- module( jupyter,
|
||||
% [jupyter_query/3,
|
||||
% errors/2,
|
||||
% ready/2,
|
||||
% completion/2,
|
||||
% ]
|
||||
%% ).
|
||||
:- module( jupyter,
|
||||
[jupyter_query/3,
|
||||
blank/1
|
||||
]
|
||||
).
|
||||
:- use_module(library(hacks)).
|
||||
|
||||
:- use_module(library(lists)).
|
||||
@@ -21,6 +19,7 @@
|
||||
:- use_module(library(python)).
|
||||
:- use_module(library(yapi)).
|
||||
:- use_module(library(complete)).
|
||||
:- use_module(library(verify)).
|
||||
|
||||
:- python_import(sys).
|
||||
|
||||
@@ -92,103 +91,6 @@ streams(true) :-
|
||||
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( _ ).
|
||||
|
||||
|
||||
:- if( current_prolog_flag(apple, true) ).
|
||||
|
||||
|
@@ -5,14 +5,12 @@
|
||||
*/
|
||||
|
||||
|
||||
% :- module( verify,
|
||||
% [all_clear/4,
|
||||
% errors/2,
|
||||
% ready/2,
|
||||
s % completion/2,
|
||||
% ]
|
||||
%% ).
|
||||
:- module( verify,
|
||||
[errors/2,
|
||||
ready/2]
|
||||
).
|
||||
:- use_module(library(hacks)).
|
||||
:- use_module(library(jupyter)).
|
||||
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(maplist)).
|
||||
@@ -20,43 +18,155 @@ s % completion/2,
|
||||
:- use_module(library(python)).
|
||||
:- use_module(library(yapi)).
|
||||
|
||||
:- python_import(sys).
|
||||
|
||||
p_errors( Errors, Cell) :-
|
||||
blank( Cell ),
|
||||
!.
|
||||
p_errors( Errors, Cell) :-
|
||||
no_errors( Errors , Cell ).
|
||||
ready( Engine, Query) :-
|
||||
errors( Engine , Cell ),
|
||||
Es := Engine.errors,
|
||||
Es == [].
|
||||
|
||||
no_errors( _Errors , Text ) :-
|
||||
|
||||
|
||||
errors( _Engine , Text ) :-
|
||||
blank(Text).
|
||||
no_errors( Errors , Text ) :-
|
||||
setup_call_cleanup(
|
||||
open_esh( Errors , Text, Stream),
|
||||
esh(Errors , Stream),
|
||||
close_esh( Errors , Stream )
|
||||
).
|
||||
|
||||
syntax(_Errors , E) :- writeln(user_error, E), fail.
|
||||
syntax(Errors , error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
|
||||
Errors.errors := [t(Cause,LN,CharPos,Details)] + Errors.errors,
|
||||
!.
|
||||
syntax(_Errors , E) :- throw(E).
|
||||
|
||||
open_esh(_Errors , Text, Stream) :-
|
||||
open_mem_read_stream( Text, Stream ).
|
||||
|
||||
esh(Errors , Stream) :-
|
||||
repeat,
|
||||
catch(
|
||||
read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ),
|
||||
Error,
|
||||
syntax(Errors , Error)
|
||||
),
|
||||
Cl == end_of_file,
|
||||
!.
|
||||
errors( Engine , Text ) :-
|
||||
b_setval(jupyter, Engine),
|
||||
setup_call_cleanup(
|
||||
open_esh( Engine , Text, Stream, Name ),
|
||||
esh(Engine , Name, Stream),
|
||||
close_esh( Engine , Stream )
|
||||
),
|
||||
fail.
|
||||
errors( _Engine , _Text ).
|
||||
|
||||
open_esh(Engine , Text, Stream, Name) :-
|
||||
Engine.errors := [],
|
||||
b_setval( jupyter, Engine),
|
||||
Name := Engine.stream_name,
|
||||
open_mem_read_stream( Text, Stream ).
|
||||
|
||||
esh(Engine , Name, Stream) :-
|
||||
repeat,
|
||||
catch(
|
||||
read_clause(Stream, Cl,[]),
|
||||
E=error(C,E),
|
||||
p_message(C,E)
|
||||
),
|
||||
Cl == end_of_file,
|
||||
!.
|
||||
|
||||
|
||||
close_esh( _Engine , Stream ) :-
|
||||
close(Stream).
|
||||
|
||||
close_esh( _Errors , Stream ) :-
|
||||
close(Stream).
|
||||
|
||||
p_message(Severity, Error) :-
|
||||
writeln((Severity->Error)),
|
||||
catch( b_getval(jupyter, Engine), _, fail ),
|
||||
p_message(Severity, Engine, Error).
|
||||
|
||||
p_message( _Severity, Engine, 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).
|
||||
Engine.errors := [t(Cause,LN,CharPos,Details)] + Engine.errors,
|
||||
!.
|
||||
p_message(error, Engine, E) :-
|
||||
writeln(E),
|
||||
!.
|
||||
p_message(warning, Engine, E) :-
|
||||
writeln(E),
|
||||
!.
|
||||
p_message(error, Engine, E) :-
|
||||
Engine.errors := [E] + Engine.errors.
|
||||
p_message(warning, Engine, E) :-
|
||||
Engine.errors := [E] + Engine.errors.
|
||||
%% 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 syntax_error/4, undo/1.
|
||||
|
||||
%%
|
||||
%% 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( _ ).
|
||||
|
@@ -114,7 +114,7 @@ class YAPInputSplitter(InputSplitter):
|
||||
if not line:
|
||||
line = text.rstrip()
|
||||
self.errors = []
|
||||
engine.mgoal(errors(self, line),"user",True)
|
||||
engine.mgoal(errors(self, line),"verify",True)
|
||||
return self.errors != []
|
||||
|
||||
|
||||
@@ -528,7 +528,7 @@ class YAPRun:
|
||||
return self.errors
|
||||
self.errors=[]
|
||||
(text,_,_,_) = self.clean_end(text)
|
||||
self.yapeng.mgoal(errors(self,text),"user",True)
|
||||
self.yapeng.mgoal(errors(self,text),"verify",True)
|
||||
return self.errors
|
||||
|
||||
def jupyter_query(self, s):
|
||||
@@ -653,6 +653,7 @@ class YAPRun:
|
||||
# except SyntaxError:
|
||||
# preprocessing_exc_tuple = self.shell.syntax_error() # sys.exc_info()
|
||||
cell = raw_cell # cell has to exist so it can be stored/logged
|
||||
self.yapeng.mgoal(streams(True),"jupyter", True)
|
||||
for i in self.syntaxErrors(raw_cell):
|
||||
try:
|
||||
(what,lin,_,text) = i
|
||||
@@ -679,6 +680,7 @@ class YAPRun:
|
||||
# compiler
|
||||
# compiler = self.shell.compile if shell_futures else CachingCompiler()
|
||||
cell_name = str( self.shell.execution_count)
|
||||
engine.stream_name = cell_name
|
||||
if cell[0] == '%':
|
||||
if cell[1] == '%':
|
||||
linec = False
|
||||
@@ -707,7 +709,6 @@ class YAPRun:
|
||||
self.shell.displayhook.exec_result = self.result
|
||||
has_raised = False
|
||||
try:
|
||||
self.yapeng.mgoal(streams(True),"user", True)
|
||||
self.bindings = dicts = []
|
||||
if cell.strip('\n \t'):
|
||||
#create a Trace object, telling it what to ignore, and whether to
|
||||
@@ -732,9 +733,9 @@ class YAPRun:
|
||||
except Exception as e:
|
||||
has_raised = True
|
||||
self.result.result = False
|
||||
self.yapeng.mgoal(streams(False),"user", True)
|
||||
self.yapeng.mgoal(streams(False),"jupyter", True)
|
||||
|
||||
self.yapeng.mgoal(streams(False),"user", True)
|
||||
self.yapeng.mgoal(streams(False),"jupyter", True)
|
||||
self.shell.last_execution_succeeded = not has_raised
|
||||
|
||||
# Reset this so later displayed values do not modify the
|
||||
|
@@ -203,7 +203,7 @@ class YAPKernel(KernelBase):
|
||||
self._forward_input(allow_stdin)
|
||||
|
||||
reply_content = {}
|
||||
import trace;
|
||||
# import trace;
|
||||
try:
|
||||
res = shell.run_cell(code, store_history=store_history, silent=silent)
|
||||
finally:
|
||||
|
Reference in New Issue
Block a user