error
This commit is contained in:
		| @@ -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) ). | ||||
|  | ||||
|   | ||||
		Reference in New Issue
	
	Block a user