| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | /** | 
					
						
							| 
									
										
										
										
											2019-02-13 09:44:24 +00:00
										 |  |  |   * @file verify.yap | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |   * | 
					
						
							|  |  |  |   * @brief JUpyter support. | 
					
						
							|  |  |  |   */ | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |  %%  :- module( verify, | 
					
						
							|  |  |  | %%              [errors/2, | 
					
						
							|  |  |  | %%               ready/2] | 
					
						
							|  |  |  | %%                       ). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | :- use_module(library(hacks)). | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | %% :- use_module(library(jupyter)). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | :-	 use_module(library(lists)). | 
					
						
							|  |  |  | :-	 use_module(library(maplist)). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2019-02-27 04:23:21 +00:00
										 |  |  | %% :-	 use_module(library(python)). | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | %% :-	 use_module(library(yapi)). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | :- dynamic jupyter/1. | 
					
						
							|  |  |  | jupyter( []). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | ready( Engine, Query) :- | 
					
						
							| 
									
										
										
										
											2018-10-15 23:59:08 +01:00
										 |  |  |      errors( Engine , Query ), | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |      Es := Engine.errors, | 
					
						
							| 
									
										
										
										
											2019-02-27 04:23:21 +00:00
										 |  |  |       Es \== []. | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | errors( _Engine , Text ) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |     blank(Text), | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |     !. | 
					
						
							|  |  |  | errors( Engine , Text ) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | %start_low_level_trace, | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     setup_call_cleanup( | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |        	open_esh( Engine , Text, Stream, Name ), | 
					
						
							|  |  |  |        	 esh(Engine , Name, Stream), | 
					
						
							|  |  |  |        	close_esh( Engine , Stream ) | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     ), | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |     fail. | 
					
						
							|  |  |  | errors( _Engine , _Text ). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | open_esh(Engine , Text, Stream, Name) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |     Engine.errors := [], | 
					
						
							|  |  |  | 	   retractall(jupyter(_)), | 
					
						
							|  |  |  | 	   assertz(jupyter(Engine)), | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |     b_setval( jupyter, Engine), | 
					
						
							|  |  |  |     Name := Engine.stream_name, | 
					
						
							|  |  |  |     open_mem_read_stream( Text, Stream ). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-10-15 23:59:08 +01:00
										 |  |  | esh(Engine , _Name, Stream) :- | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |   repeat, | 
					
						
							|  |  |  |   catch( | 
					
						
							| 
									
										
										
										
											2018-10-15 23:59:08 +01:00
										 |  |  |       read_clause(Stream, Cl, [ syntax_errors(dec10)]), | 
					
						
							|  |  |  |       error(C,E), | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |       p3_message(C,Engine,E) | 
					
						
							|  |  |  |   ), | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |   Cl == end_of_file, | 
					
						
							|  |  |  |   !. | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | :- multifile user:portray_message/2. | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | user:portray_message(S,E) :- | 
					
						
							|  |  |  | jupyter(En), | 
					
						
							|  |  |  | 			   En \= [], | 
					
						
							|  |  |  | 			   python_clear_errors, | 
					
						
							|  |  |  | 			   p3_message(S,En,E). | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | close_esh( _Engine , Stream ) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | 	   retractall(jupyter(_)), | 
					
						
							|  |  |  | 	   assertz(jupyter([])), | 
					
						
							| 
									
										
										
										
											2019-03-26 09:40:54 +00:00
										 |  |  | 	   close(Stream), | 
					
						
							|  |  |  | 	   python_clear_errors. | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | p3_message( _Severity,  Engine, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :- | 
					
						
							| 
									
										
										
										
											2018-10-15 23:59:08 +01:00
										 |  |  |     python_clear_errors, | 
					
						
							|  |  |  |     !, | 
					
						
							|  |  |  |     Engine.errors := [t(Cause,LN,CharPos,Details)]+Engine.errors . | 
					
						
							|  |  |  | p3_message(error, _Engine, _E) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |      python_clear_errors, | 
					
						
							|  |  |  |      !. | 
					
						
							| 
									
										
										
										
											2018-10-15 23:59:08 +01:00
										 |  |  | p3_message(warning, _Engine, _E) :- | 
					
						
							|  |  |  |     !. | 
					
						
							|  |  |  | p3_message(error, Engine, E) :- | 
					
						
							|  |  |  |     Engine.errors := [E] + Engine.errors. | 
					
						
							|  |  |  | p3_message(warning, Engine, E) :- | 
					
						
							|  |  |  |     Engine.errors := [E] + Engine.errors. | 
					
						
							|  |  |  | %% ready(_Self, Line ) :- | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | %%             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. | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | %% | 
					
						
							|  |  |  | %% open_events(Self, Text, Stream) :- | 
					
						
							|  |  |  | %% 	Self.errors := [], | 
					
						
							|  |  |  | %% 	nb_setval( jupyter, on), | 
					
						
							|  |  |  | %%     open_mem_read_stream( Text, Stream ). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | %% :- initialization( nb_setval( jupyter, off ) ). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  | %% 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( _ ). |