This commit is contained in:
Vitor Santos Costa 2019-03-27 16:31:31 +00:00
parent 78473ddd2c
commit c50367325e
3 changed files with 99 additions and 105 deletions

View File

@ -3,16 +3,16 @@
%% @brief support yap shell %% @brief support yap shell
%% %%
:- module(yapi, [ %% :- module(yapi, [
python_ouput/0, %% python_ouput/0,
show_answer/2, %% show_answer/2,
show_answer/3, %% show_answer/3,
yap_query/4, %% yap_query/4,
python_query/2, %% python_query/2,
python_query/3, %% python_query/3,
python_import/1, %% python_import/1,
yapi_query/2 %% yapi_query/2
]). %% ]).
%:- yap_flag(verbose, silent). %:- yap_flag(verbose, silent).

View File

@ -6,22 +6,22 @@
*/ */
%:- yap_flag(gc_trace,verbose). %:- yap_flag(gc_trace,verbose).
:- module( jupyter, %% :- module( jupyter,
[jupyter_query/3, %% [jupyter_query/3,
jupyter_query/4, %% jupyter_query/4,
op(100,fy,('$')), %% op(100,fy,('$')),
op(950,fy,:=), %% op(950,fy,:=),
op(950,yfx,:=), %% op(950,yfx,:=),
% op(950,fx,<-), %% % op(950,fx,<-),
% op(950,yfx,<-), %% % op(950,yfx,<-),
op(50, yf, []), %% op(50, yf, []),
op(50, yf, '()'), %% op(50, yf, '()'),
op(100, xfy, '.'), %% op(100, xfy, '.'),
op(100, fy, '.'), %% op(100, fy, '.'),
blank/1, %% blank/1,
streams/1 %% streams/1
] %% ]
). %% ).
:- use_module(library(hacks)). :- use_module(library(hacks)).
@ -37,15 +37,10 @@
:- python_import(sys). :- python_import(sys).
:- meta_predicate jupyter_query(+,:,+,-), jupyter_query(+,:,+). %:- meta_predicate jupyter_query(+,:,+,-), jupyter_query(+,:,+).
jupyter_query(Caller, Cell, Line, Bindings ) :- jupyter_query(Caller, Cell, Line, Bindings ) :-
gated_call( jupyter_cell(Caller, Cell, Line, Bindings).
streams(true),
jupyter_cell(Caller, Cell, Line, Bindings),
Port,
next_streams( Caller, Port, Bindings )
).
jupyter_query(Caller, Cell, Line ) :- jupyter_query(Caller, Cell, Line ) :-
jupyter_query( Caller, Cell, Line, _Bindings ). jupyter_query( Caller, Cell, Line, _Bindings ).
@ -58,8 +53,8 @@ next_streams( _Caller, answer, _Bindings ) :-
!. !.
next_streams(_, redo, _ ) :- next_streams(_, redo, _ ) :-
!. !.
next_streams( _, _, _ ) :- next_streams( _, _, _ ). % :-
streams(false). % streams(false).
@ -105,9 +100,8 @@ jupyter_consult(Cell) :-
load_files(user:Stream,[stream(Stream)| Options]) load_files(user:Stream,[stream(Stream)| Options])
), ),
error(A,B), error(A,B),
(close(Stream), system_error(A,B)) system_error(A,B)
), ),
close(Stream),
fail. fail.
jupyter_consult(_Cell). jupyter_consult(_Cell).

View File

@ -614,6 +614,13 @@ class YAPRun(InteractiveShell):
`result : :class:`ExecutionResult` `result : :class:`ExecutionResult`
""" """
if store_history:
# Write output to the database. Does nothing unless
# history output logging is enabled.
self.shell.history_manager.store_output(self.shell.execution_count)
# Each cell is a *single* input, regardless of how many lines it has
self.shell.execution_count += 1
# construct a query from a one-line string # construct a query from a one-line string
# q is opaque to Python # q is opaque to Python
# vs is the list of variables # vs is the list of variables
@ -649,8 +656,6 @@ class YAPRun(InteractiveShell):
# # Display the exception if input processing failed. # # Display the exception if input processing failed.
if preprocessing_exc_tuple is not None: if preprocessing_exc_tuple is not None:
self.showtraceback(preprocessing_exc_tuple) self.showtraceback(preprocessing_exc_tuple)
if store_history:
self.shell.execution_count += 1
return self.error_before_exec(preprocessing_exc_tuple[2]) return self.error_before_exec(preprocessing_exc_tuple[2])
# Our own compiler remembers the __future__ environment. If we want to # Our own compiler remembers the __future__ environment. If we want to
@ -695,7 +700,7 @@ class YAPRun(InteractiveShell):
# can fill in the output value. # can fill in the output value.
self.shell.displayhook.exec_result = result self.shell.displayhook.exec_result = result
(program,squery,_ ,howmany) = self.prolog_cell(cell) (program,squery,_ ,howmany) = self.prolog_cell(cell)
print(program, squery, howmany) print("program",program, "q", squery, "h",howmany)
if howmany <= 0 and not program: if howmany <= 0 and not program:
return result return result
if self.syntaxErrors(program+squery+".\n") : if self.syntaxErrors(program+squery+".\n") :
@ -741,13 +746,6 @@ class YAPRun(InteractiveShell):
if not silent: if not silent:
self.shell.events.trigger('post_run_cell') self.shell.events.trigger('post_run_cell')
if store_history:
# Write output to the database. Does nothing unless
# history output logging is enabled.
self.shell.history_manager.store_output(self.shell.execution_count)
# Each cell is a *single* input, regardless of how many lines it has
self.shell.execution_count += 1
self.engine.mgoal(streams(False),"user", True) self.engine.mgoal(streams(False),"user", True)
return return
@ -788,7 +786,7 @@ def pcell(s):
line = sl[-i-1] line = sl[-i-1]
if line.strip() == '': if line.strip() == '':
break break
query = line+'\n\n'+query query = line+'\n'+query
i+=1 i+=1
reps = 1 reps = 1
if query: if query:
@ -817,15 +815,17 @@ def pcell(s):
program = '' program = ''
while i<l: while i<l:
line = sl[-i-1] line = sl[-i-1]
program = line+'\n\n'+program program = line+'\n'+program
i+=1 i+=1
return (program, query, loop, reps) return (program, query, loop, reps)
except Exception as e: except Exception as e:
try: try:
(etype, value, tb) = e (etype, value, tb) = e
traceback.print_exception(etype, value, tb) traceback.print_exception(etype, value, tb)
return ('','','',-1)
except: except:
print(e) print(e)
return ('','','',-1)