| 
									
										
										
										
											2018-07-18 17:36:01 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-06-03 23:59:17 +01:00
										 |  |  | /** | 
					
						
							| 
									
										
										
										
											2018-05-28 09:31:59 +01:00
										 |  |  |   * @file jupyter.yap4py | 
					
						
							|  |  |  |   * | 
					
						
							|  |  |  |   * @brief JUpyter support. | 
					
						
							|  |  |  |   */ | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | :- yap_flag(gc_trace,verbose). | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | /* | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |   :- module( jupyter, | 
					
						
							|  |  |  |               [jupyter_query/3, | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |                blank/1, | 
					
						
							|  |  |  | 	       streams/1 | 
					
						
							| 
									
										
										
										
											2018-07-17 11:43:57 +01:00
										 |  |  |            ] | 
					
						
							|  |  |  |             ). | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | */ | 
					
						
							| 
									
										
										
										
											2018-05-28 09:31:59 +01:00
										 |  |  | :- use_module(library(hacks)). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-01-18 14:47:27 +00:00
										 |  |  | :-	 use_module(library(lists)). | 
					
						
							|  |  |  | :-	 use_module(library(maplist)). | 
					
						
							| 
									
										
										
										
											2018-05-28 09:31:59 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | %% :-	 reexport(library(python)). | 
					
						
							|  |  |  | %% :-	 reexport(library(yapi)). | 
					
						
							|  |  |  | %% :-	 reexport(library(complete)). | 
					
						
							|  |  |  | %% :-	 reexport(library(verify)). | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											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 ) :- | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  |     jupyter_cell(Caller, Cell, Line). | 
					
						
							| 
									
										
										
										
											2017-12-14 18:40:22 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-06-05 11:20:39 +01:00
										 |  |  | jupyter_cell(_Caller, Cell, _Line) :- | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 	jupyter_consult(Cell),	%stack_dump, | 
					
						
							| 
									
										
										
										
											2017-12-14 18:40:22 +00:00
										 |  |  | 	fail. | 
					
						
							| 
									
										
										
										
											2018-07-23 17:13:51 +01:00
										 |  |  | jupyter_cell( _Caller, _, ¨¨ ) :- !. | 
					
						
							| 
									
										
										
										
											2018-03-02 21:18:24 +00:00
										 |  |  | jupyter_cell( _Caller, _, Line ) :- | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | 	blank( Line ), | 
					
						
							|  |  |  | 	!. | 
					
						
							| 
									
										
										
										
											2018-07-21 23:29:01 +01:00
										 |  |  | jupyter_cell(Caller, _, Line ) :- | 
					
						
							| 
									
										
										
										
											2018-07-23 17:13:51 +01:00
										 |  |  |   Query = Caller, | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |     catch( | 
					
						
							| 
									
										
										
										
											2018-07-23 17:13:51 +01:00
										 |  |  | 	python_query(Query,Line), | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | 	E=error(A,B), | 
					
						
							|  |  |  | 	 system_error(A,B) | 
					
						
							|  |  |  |     ). | 
					
						
							| 
									
										
										
										
											2018-06-01 08:37:25 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-06-01 13:22:13 +01:00
										 |  |  | restreams(call) :- | 
					
						
							| 
									
										
										
										
											2018-06-01 08:37:25 +01:00
										 |  |  |     streams(true). | 
					
						
							|  |  |  | restreams(fail) :- | 
					
						
							|  |  |  |     streams(false). | 
					
						
							| 
									
										
										
										
											2018-06-01 13:22:13 +01:00
										 |  |  | restreams(answer). | 
					
						
							| 
									
										
										
										
											2018-06-01 08:37:25 +01:00
										 |  |  | restreams(exit) :- | 
					
						
							|  |  |  |     streams(false). | 
					
						
							| 
									
										
										
										
											2018-06-01 13:22:13 +01:00
										 |  |  | restreams(!). | 
					
						
							|  |  |  | restreams(external_exception(_)). | 
					
						
							|  |  |  | restreams(exception). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | jupyter_consult(Text) :- | 
					
						
							|  |  |  | 	blank( Text ), | 
					
						
							|  |  |  | 	!. | 
					
						
							|  |  |  | jupyter_consult(Cell) :- | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | %	Name = 'Inp', | 
					
						
							|  |  |  | %	stream_property(Stream, file_name(Name) ), | 
					
						
							| 
									
										
										
										
											2018-06-05 11:20:39 +01:00
										 |  |  | %	setup_call_cleanup( | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |     catch( | 
					
						
							|  |  |  | 	( | 
					
						
							|  |  |  | 	    Options = [], | 
					
						
							|  |  |  | 	    open_mem_read_stream( Cell, Stream), | 
					
						
							|  |  |  | 	    load_files(user:'jupyter cell',[stream(Stream)| Options]) | 
					
						
							|  |  |  | 	), | 
					
						
							|  |  |  | 	E=error(A,B), | 
					
						
							|  |  |  | 	(close(Stream), system_error(A,B)) | 
					
						
							|  |  |  |     ), | 
					
						
							|  |  |  |     fail. | 
					
						
							|  |  |  | jupyter_consult(_Cell). | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | 
 | 
					
						
							|  |  |  | blank(Text) :- | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  |     atom(Text), | 
					
						
							|  |  |  |     !, | 
					
						
							| 
									
										
										
										
											2017-12-20 00:29:15 +00:00
										 |  |  | 	atom_codes(Text, L), | 
					
						
							| 
									
										
										
										
											2018-06-05 11:20:39 +01:00
										 |  |  | 	maplist( code_type(space), L). | 
					
						
							| 
									
										
										
										
											2018-07-10 23:21:19 +01:00
										 |  |  | blank(Text) :- | 
					
						
							|  |  |  |     string(Text), | 
					
						
							|  |  |  |     !, | 
					
						
							|  |  |  |     string_codes(Text, L), | 
					
						
							|  |  |  |     maplist( code_type(space), L). | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  |  streams(false) :- | 
					
						
							| 
									
										
										
										
											2018-07-09 01:57:13 +01:00
										 |  |  |     close(user_input), | 
					
						
							|  |  |  |     close(user_output), | 
					
						
							|  |  |  |     close(user_error). | 
					
						
							| 
									
										
										
										
											2018-03-12 15:11:59 +00:00
										 |  |  | streams(true) :- | 
					
						
							| 
									
										
										
										
											2018-07-31 15:18:56 +01:00
										 |  |  |     open('/python/input', read, _Input, [alias(user_input),bom(false),script(false)]), | 
					
						
							| 
									
										
										
										
											2018-07-27 11:11:04 +01:00
										 |  |  |     open('/python/sys.stdout', append, _Output, [alias(user_output)]), | 
					
						
							|  |  |  |     open('/python/sys.stderr', append, _Error, [alias(user_error)]). | 
					
						
							| 
									
										
										
										
											2017-08-21 12:36:48 +01:00
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-05-21 14:45:24 +01:00
										 |  |  | 
 | 
					
						
							|  |  |  | :- if(  current_prolog_flag(apple, true) ). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | :- putenv( 'LC_ALL', 'en_us:UTF-8'). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | plot_inline :- | 
					
						
							|  |  |  | 	X := self.inline_plotting, | 
					
						
							|  |  |  | 	nb_setval(inline, X ), | 
					
						
							|  |  |  | 	X = true, | 
					
						
							|  |  |  | 	!, | 
					
						
							|  |  |  | 	:= ( | 
					
						
							|  |  |  | 	   import( matplotlib ), | 
					
						
							|  |  |  | 	   matplotlib.use( `nbagg` ) | 
					
						
							|  |  |  | 	   ). | 
					
						
							|  |  |  | 
 | 
					
						
							|  |  |  | :- endif. | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2018-07-21 01:56:48 +01:00
										 |  |  | %y:- ( start_low_level_trace ). |