This commit is contained in:
Vitor Santos Costa
2018-07-21 01:56:48 +01:00
parent abc11dcfaa
commit 562e9e5af3
28 changed files with 1266 additions and 1567 deletions

View File

@@ -4,12 +4,12 @@
* @brief Prolog completer.
*/
:- module( completer,
[completions/2 ]).
%% %% :- module( completer,
%% %% [completions/2 ]).
:- use_module(library(lists)).
:- use_module(library(maplist)).
:- use_module(library(python)).
:- use_module(library(python)).
%% completions( +Text, +PythonCell )
%

View File

@@ -6,36 +6,38 @@
*/
:- yap_flag(gc_trace,verbose).
/*
:- module( jupyter,
[jupyter_query/3,
blank/1
blank/1,
streams/1
]
).
*/
:- use_module(library(hacks)).
:- use_module(library(lists)).
:- use_module(library(maplist)).
:- reexport(library(python)).
:- reexport(library(yapi)).
:- reexport(library(complete)).
:- reexport(library(verify)).
%% :- reexport(library(python)).
%% :- reexport(library(yapi)).
%% :- reexport(library(complete)).
%% :- reexport(library(verify)).
:- python_import(sys).
jupyter_query(Caller, Cell, Line ) :-
jupyter_cell(Caller, Cell, Line).
jupyter_cell(Caller, Cell, Line).
jupyter_cell(_Caller, Cell, _Line) :-
jupyter_consult(Cell), %stack_dump,
fail.
jupyter_cell( _Caller, _, '' ) :- !.
jupyter_cell( _Caller, _, `` ) :- !.
jupyter_cell( _Caller, _, Line ) :-
blank( Line ),
!.
jupyter_cell( Caller, _, Line ) :-
Self := Caller.query,
jupyter_cell(Self, _, Line ) :-
catch(
python_query(Self,Line),
E=error(A,B),
@@ -83,7 +85,8 @@ blank(Text) :-
string_codes(Text, L),
maplist( code_type(space), L).
streams(false) :-
streams(false) :-
close(user_input),
close(user_output),
close(user_error).
@@ -109,4 +112,4 @@ plot_inline :-
:- endif.
%:- ( start_low_level_trace ).
%y:- ( start_low_level_trace ).

View File

@@ -5,19 +5,22 @@
*/
:- module( verify,
[errors/2,q
ready/2]
).
%% :- module( verify,
%% [errors/2,
%% ready/2]
%% ).
:- use_module(library(hacks)).
:- use_module(library(jupyter)).
%% :- use_module(library(jupyter)).
:- use_module(library(lists)).
:- use_module(library(maplist)).
:- use_module(library(python)).
:- use_module(library(yapi)).
:- use_module(library(python)).
%% :- use_module(library(yapi)).
:- dynamic jupyter/1.
jupyter( []).
ready( Engine, Query) :-
errors( Engine , Cell ),
@@ -27,10 +30,10 @@ ready( Engine, Query) :-
errors( _Engine , Text ) :-
blank(Text).
blank(Text),
!.
errors( Engine , Text ) :-
jupyter..shell := Engine,
%start_low_level_trace,
setup_call_cleanup(
open_esh( Engine , Text, Stream, Name ),
esh(Engine , Name, Stream),
@@ -40,50 +43,55 @@ errors( Engine , Text ) :-
errors( _Engine , _Text ).
open_esh(Engine , Text, Stream, Name) :-
Engine.errors := [],
Engine.errors := [],
retractall(jupyter(_)),
assertz(jupyter(Engine)),
b_setval( jupyter, Engine),
Name := Engine.stream_name,
open_mem_read_stream( Text, Stream ).
esh(Engine , Name, Stream) :-
b_setval(code,python),
repeat,
catch(
( read_clause(Stream, Cl, [ syntax_errors(fail)]),
writeln(cl:Cl),
read_clause(Stream, Cl, [ syntax_errors(dec10)]),
error(C,E),
p_message(C,E)
p3_message(C,Engine,E)
),
Cl == end_of_file,
!.
user:print_message() :- p_message
:- multifile user:portray_message/2.
user:portray_message(S,E) :-
jupyter(En),
En \= [],
python_clear_errors,
p3_message(S,En,E).
close_esh( _Engine , Stream ) :-
b_delete
retractall(jupyter(_)),
assertz(jupyter([])),
close(Stream).
p_message(Severity, Error) :-
writeln((Severity->Error)),
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) :-
p3_message( _Severity, Engine, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
python_clear_errors,
!,
writeln(E),
NE := [t(Cause,LN,CharPos,Details)]+Engine.errors,
writeln(E),
writeln(NE),
Engine.errors := NE.
p3_message(error, Engine, E) :-
python_clear_errors,
!.
p3_message(warning, Engine, E) :-
!.
p_message(error, Engine, E) :-
p3_message(error, Engine, E) :-
Engine.errors := [E] + Engine.errors.
p_message(warning, Engine, E) :-
p3_message(warning, Engine, E) :-
Engine.errors := [E] + Engine.errors.
%% ready(_Self, Line ) :-
%% blank( Line ),
@@ -173,3 +181,4 @@ p_message( _Severity, Engine, error(syntax_error(Cause),info(between(_,LN,_), _
%% Self.errors := [t(C,L,N,A)] + Self.errors,
%% fail.
%% close_events( _ ).