| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | /** | 
					
						
							|  |  |  |   * @file jupyter.yap4py | 
					
						
							|  |  |  |   * | 
					
						
							|  |  |  |   * @brief JUpyter support. | 
					
						
							|  |  |  |   */ | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  |   % :- module( verify, | 
					
						
							|  |  |  |   %           [all_clear/4, | 
					
						
							|  |  |  |   %            errors/2, | 
					
						
							|  |  |  |   %            ready/2, | 
					
						
							|  |  |  | s  %           completion/2, | 
					
						
							|  |  |  |   %         ] | 
					
						
							|  |  |  | %%            ). | 
					
						
							|  |  |  | :- use_module(library(hacks)). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | :-	 use_module(library(lists)). | 
					
						
							|  |  |  | :-	 use_module(library(maplist)). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | :-	 use_module(library(python)). | 
					
						
							|  |  |  | :-	 use_module(library(yapi)). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | :- python_import(sys). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | p_errors( Errors, Cell) :- | 
					
						
							|  |  |  |   blank( Cell ), | 
					
						
							|  |  |  |   !. | 
					
						
							|  |  |  | p_errors( Errors, Cell) :- | 
					
						
							|  |  |  |     no_errors( Errors , Cell ). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | no_errors( _Errors , Text ) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     blank(Text). | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | no_errors( Errors , Text ) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     setup_call_cleanup( | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |        	open_esh( Errors , Text, Stream), | 
					
						
							|  |  |  |        	esh(Errors , Stream), | 
					
						
							|  |  |  |        	close_esh( Errors , Stream ) | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     ). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | 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, | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 							!. | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | syntax(_Errors , E) :- throw(E). | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | open_esh(_Errors , Text, Stream) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 	     open_mem_read_stream( Text, Stream ). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | esh(Errors , Stream) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     repeat, | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |   catch( | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 	read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ), | 
					
						
							|  |  |  | 	Error, | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | 	syntax(Errors , Error) | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     ), | 
					
						
							|  |  |  |     Cl == end_of_file, | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |     !. | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | close_esh( _Errors , Stream ) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     close(Stream). |