| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | /** | 
					
						
							|  |  |  |  * @file jupyter.yap | 
					
						
							|  |  |  |  * | 
					
						
							|  |  |  |  * @brief allow interaction between Jupyter and YAP. | 
					
						
							|  |  |  |  * | 
					
						
							|  |  |  |  * @long The code in here: | 
					
						
							|  |  |  |  * - establishes communication between Prolog and Python Streams | 
					
						
							|  |  |  |  * - inputs Prolog code and queries | 
					
						
							|  |  |  |  * - supports completion of Prolog programs. | 
					
						
							|  |  |  |  * - | 
					
						
							|  |  |  |  */ | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  |   % :- module( jupyter, | 
					
						
							|  |  |  |   %            [jupyter_query/3, | 
					
						
							|  |  |  |   %            errors/2, | 
					
						
							|  |  |  |   %            ready/2, | 
					
						
							|  |  |  |   %           completion/2, | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  |   %         ] | 
					
						
							|  |  |  | %%            ). | 
					
						
							|  |  |  | :- [library(hacks)]. | 
					
						
							| 
									
										
										
										
											2018-01-05 16:57:38 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | :-	 reexport(library(yapi)). | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | :-	 use_module(library(lists)). | 
					
						
							|  |  |  | :-	 use_module(library(maplist)). | 
					
						
							|  |  |  | :-	 use_module(library(python)). | 
					
						
							| 
									
										
										
										
											2018-01-05 16:57:38 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | :- python_import(sys). | 
					
						
							| 
									
										
										
										
											2018-01-05 16:57:38 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | jupyter_query(Caller, Cell, Line ) :- | 
					
						
							|  |  |  | 	jupyter_cell(Caller, Cell, Line). | 
					
						
							| 
									
										
										
										
											2017-12-14 18:40:22 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | jupyter_cell(_Caller, Cell, _) :- | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	jupyter_consult(Cell),	%stack_dump, | 
					
						
							| 
									
										
										
										
											2017-12-14 18:40:22 +00:00
										 |  |  | 	fail. | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | jupyter_cell( _Caller, _, Line ) :- | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | 	blank( Line ), | 
					
						
							|  |  |  | 	!. | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | jupyter_cell( _Caller, _, [] ) :- !. | 
					
						
							|  |  |  | jupyter_cell( Caller, _, Line ) :- | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	Self := Caller.query, | 
					
						
							|  |  |  | 	python_query( Self, Line ). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | jupyter_consult(Text) :- | 
					
						
							|  |  |  | 	blank( Text ), | 
					
						
							|  |  |  | 	!. | 
					
						
							|  |  |  | jupyter_consult(Cell) :- | 
					
						
							|  |  |  | 	open_mem_read_stream( Cell, Stream), | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | %	Name = 'Inp', | 
					
						
							|  |  |  | %	stream_property(Stream, file_name(Name) ), | 
					
						
							|  |  |  | 	load_files(user:'jupyter cell',[stream(Stream)]), !. | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | 	%should load_files  close? | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | blank(Text) :- | 
					
						
							|  |  |  | 	atom_codes(Text, L), | 
					
						
							|  |  |  | 	maplist( blankc, L). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | blankc(' '). | 
					
						
							|  |  |  | blankc('\n'). | 
					
						
							|  |  |  | blankc('\t'). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | streams(false) :- | 
					
						
							| 
									
										
										
										
											2018-03-19 11:43:14 +00:00
										 |  |  | nb_setval(jupyter_cell, false), | 
					
						
							| 
									
										
										
										
											2018-03-17 10:38:56 +00:00
										 |  |  | 	flush_output, | 
					
						
							|  |  |  | 	forall( | 
					
						
							|  |  |  | 	       stream_property( S, mode(_) ), | 
					
						
							|  |  |  | 	       close(S) | 
					
						
							|  |  |  | 	      ). | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | streams(true) :- | 
					
						
							| 
									
										
										
										
											2018-03-19 11:43:14 +00:00
										 |  |  |   nb_setval(jupyter_cell, true), | 
					
						
							|  |  |  |   open('/python/input', read, _Input, [alias(user_input),bom(false)]), | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	open('/python/sys.stdout', append, _Output, [alias(user_output)]), | 
					
						
							|  |  |  | 	open('/python/sys.stderr', append, _Error, [alias(user_error)]), | 
					
						
							| 
									
										
										
										
											2018-03-19 11:43:14 +00:00
										 |  |  |   set_prolog_flag(user_input,_Input), | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | 	set_prolog_flag(user_output,_Output), | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	set_prolog_flag(user_error,_Error). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-02-08 10:48:02 +00:00
										 |  |  | completions(S, Self) :- | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | 	open_mem_read_stream(S, St), | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 	scan_to_list(St, Tokens), | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | 	close(St), | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 	reverse(Tokens, RTokens), | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | 	strip_final_tokens(RTokens, MyTokens), | 
					
						
							|  |  |  | 	setof( Completion, complete(MyTokens, Completion), Cs), | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | 	Self.matches := Cs. | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | strip_final_tokens(['EOT'|Ts], Ts) :- !. | 
					
						
							| 
									
										
										
										
											2017-11-13 11:02:35 +00:00
										 |  |  | strip_final_tokens( Ts, Ts ). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | complete([E,l,C,l,A|More], | 
					
						
							|  |  |  | 	 isconsult(A), | 
					
						
							|  |  |  | 	  %B = l, | 
					
						
							|  |  |  | 	  library(C,Lib), | 
					
						
							|  |  |  | 	  %D=l, | 
					
						
							|  |  |  | 	  E=atom(Prefix), | 
					
						
							|  |  |  | 	\+ arg( Rest ), | 
					
						
							|  |  |  | 	check_library( Prefix, Lib, C). | 
					
						
							|  |  |  | complete([E,l,C,l,-,'['|More], | 
					
						
							|  |  |  | 	 isconsult(A), | 
					
						
							|  |  |  | 	  %B = l, | 
					
						
							|  |  |  | 	  library(C,Lib), | 
					
						
							|  |  |  | 	  %D=l, | 
					
						
							|  |  |  | 	  E=atom(Prefix), | 
					
						
							|  |  |  | 	\+ arg( Rest ), | 
					
						
							|  |  |  | 	check_library( Prefix, Lib, C). | 
					
						
							|  |  |  | complete([C,l,A|More], | 
					
						
							|  |  |  | 	 isconsult(A), | 
					
						
							|  |  |  | 	  %B = l, | 
					
						
							|  |  |  | 	  C=atom(Prefix), | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 	\+ arg( Rest ), | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | 	file_or_library( Prefix, C). | 
					
						
							|  |  |  | complete([C,l,-,'['|More], | 
					
						
							|  |  |  | 	 isconsult(A), | 
					
						
							|  |  |  | 	  %B = l, | 
					
						
							|  |  |  | 	  C=atom(Prefix), | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 	\+ arg( Rest ), | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | 	file_or_library( Prefix, C). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | complete( [atom(F)|Rest], C) :- | 
					
						
							|  |  |  | 	\+ arg( Rest ), | 
					
						
							|  |  |  | 	predicate( F, Pred, Arity ), | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | 	cont( Arity, F, Pred, C). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | isconsult( atom(use_module) ). | 
					
						
							|  |  |  | isconsult( atom(ensure_loaded) ). | 
					
						
							|  |  |  | isconsult( atom(compile) ). | 
					
						
							|  |  |  | isconsult( atom(consult) ). | 
					
						
							|  |  |  | isconsult( atom(reconsult) ). | 
					
						
							|  |  |  | isconsult( atom(load_files) ). | 
					
						
							|  |  |  | isconsult( '['   ). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | arg([']'|_]). | 
					
						
							|  |  |  | arg([l|_]). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-11-13 11:02:35 +00:00
										 |  |  | file_or_library(F,C) :- | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | 	libsym(C0), | 
					
						
							| 
									
										
										
										
											2017-12-13 16:56:10 +00:00
										 |  |  | 	atom_cooncat(F,C,C0). | 
					
						
							| 
									
										
										
										
											2017-11-13 11:02:35 +00:00
										 |  |  | file_or_library(F,C) :- | 
					
						
							| 
									
										
										
										
											2017-12-13 16:56:10 +00:00
										 |  |  | 	check_file(F,C). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | check_file(F0,C) :- | 
					
						
							|  |  |  | 	atom_concat('\'',F,F0), | 
					
						
							|  |  |  | 	!, | 
					
						
							|  |  |  | 	absolute_file_name( F, FF, [access(none)]  ), | 
					
						
							| 
									
										
										
										
											2017-12-13 16:56:10 +00:00
										 |  |  | 	atom_concat( FF, '*'	, Pat), | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | 	absolute_file_name( Pat, C0, [glob(true)]  ), | 
					
						
							|  |  |  | 	atom_concat(Pat,C00,C0), | 
					
						
							|  |  |  | 	atom_conct(C00,'\'',C). | 
					
						
							|  |  |  | check_file(F0,C) :- | 
					
						
							| 
									
										
										
										
											2017-12-13 16:56:10 +00:00
										 |  |  | 	atom_concat( F0, '*'	, Pat), | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 	absolute_file_name( Pat, C0, [glob(true)]  ), | 
					
						
							| 
									
										
										
										
											2017-09-06 01:09:46 +01:00
										 |  |  | 	atom_concat(Pat,C,C0). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | check_library( Lib, F, C) :- | 
					
						
							|  |  |  | 	atom_concat( F, '*'	, Pat), | 
					
						
							|  |  |  | 	LibF =.. [Lib(Pat)], | 
					
						
							|  |  |  | 	absolute_file_name( LibF, Lib, [glob(true)]  ), | 
					
						
							|  |  |  | 	file_directory_name( Lib, Name), | 
					
						
							|  |  |  | 	( atom_concat(C, '.yap', Name) -> true ; | 
					
						
							|  |  |  | 	 atom_concat(C, '.ypp', Name) -> true ; | 
					
						
							|  |  |  | 	 atom_concat(C, '.prolog', Name) -> true | 
					
						
							|  |  |  | 	). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | predicate(N,P,A) :- | 
					
						
							|  |  |  | 	system_predicate(P0/A), | 
					
						
							|  |  |  | 	atom_concat(N,P,P0). | 
					
						
							|  |  |  | predicate(N,P,A) :- | 
					
						
							|  |  |  | 	current_predicate(P0/A), | 
					
						
							|  |  |  | 	atom_concat(N,P,P0). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-12-13 16:56:10 +00:00
										 |  |  | cont(0, F, P, P0) :- | 
					
						
							| 
									
										
										
										
											2017-11-13 11:02:35 +00:00
										 |  |  | 		atom_concat( F, P, P0 ). | 
					
						
							| 
									
										
										
										
											2017-08-27 22:27:51 +01:00
										 |  |  | cont( _, F, P, PB ):- | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	atom_concat( [F, P, '(  )'], PB ). | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | ready(_Self, Line ) :- | 
					
						
							|  |  |  |             blank( Line ), | 
					
						
							|  |  |  |             !. | 
					
						
							|  |  |  | ready(Self, Line ) :- | 
					
						
							|  |  |  |     errors( Self, Line ), | 
					
						
							| 
									
										
										
										
											2018-01-27 10:17:27 +00:00
										 |  |  |     \+ syntax_error(_,_). | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-02-08 10:48:02 +00:00
										 |  |  | errors( Self, Text ) :- | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  |        	setup_call_cleanup( | 
					
						
							|  |  |  |        			   open_events( Self, Text, Stream), | 
					
						
							| 
									
										
										
										
											2018-02-25 00:29:08 +00:00
										 |  |  |        			   goals(Self, Stream), | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  |        			   close_events( Self ) | 
					
						
							|  |  |  |        	 	   ). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | clauses(_Self, Stream) :- | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  |     repeat, | 
					
						
							|  |  |  |     read_clause(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ), | 
					
						
							| 
									
										
										
										
											2018-02-25 00:29:08 +00:00
										 |  |  | %	command( Self, Cl ), | 
					
						
							|  |  |  |     Cl == end_of_file, | 
					
						
							|  |  |  |     !. | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | goals(_Self, Stream) :- | 
					
						
							| 
									
										
										
										
											2018-02-25 00:29:08 +00:00
										 |  |  |     repeat, | 
					
						
							|  |  |  |     read_term(Stream, Cl, [term_position(_Pos), syntax_errors(fail)] ), | 
					
						
							|  |  |  | %	command( Self, Cl ), | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  |     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. | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-02-24 14:39:17 +00:00
										 |  |  | 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). | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | open_events(Self, Text, Stream) :- | 
					
						
							| 
									
										
										
										
											2018-02-24 14:39:17 +00:00
										 |  |  | 	Self.errors := [], | 
					
						
							|  |  |  | 	nb_setval( jupyter, on), | 
					
						
							|  |  |  |     open_mem_read_stream( Text, Stream ). | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-02-24 14:39:17 +00:00
										 |  |  | :- initialization( nb_setval( jupyter, off ) ). | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-01-27 10:17:27 +00:00
										 |  |  | close_events( _Self ) :- | 
					
						
							| 
									
										
										
										
											2018-02-24 14:39:17 +00:00
										 |  |  | 	nb_setval( jupyter, off ), | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | 	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( _ ). | 
					
						
							| 
									
										
										
										
											2018-02-24 14:39:17 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | %:- ( start_low_level_trace ). |