From 5f9e0299eee4707078e2eb4c759ea9ab523ee0c1 Mon Sep 17 00:00:00 2001 From: Vitor Santos Costa Date: Mon, 13 Nov 2017 11:02:35 +0000 Subject: [PATCH] boot at diferent directories --- packages/python/swig/prolog/jupyter.yap | 123 ------------------ .../yap_kernel/yap_ipython/prolog/jupyter.yap | 9 +- 2 files changed, 5 insertions(+), 127 deletions(-) delete mode 100644 packages/python/swig/prolog/jupyter.yap diff --git a/packages/python/swig/prolog/jupyter.yap b/packages/python/swig/prolog/jupyter.yap deleted file mode 100644 index d06889057..000000000 --- a/packages/python/swig/prolog/jupyter.yap +++ /dev/null @@ -1,123 +0,0 @@ - -:- use_module(library(yapi)). -:- use_module(library(lists)). -:- use_module(library(maplist)). -:- use_module(library(python)). - -:- python_import(sys). - -jupyter_query(Self, Cell) :- - setup_call_cleanup( - enter_cell(Self), - python_query(Self, Cell), - exit_cell(Self) - ). - -enter_cell(_Self) :- - open('//python/sys.stdout', append, _Output, [alias(jupo)]), - open('//python/sys.stdout', append, _, [alias(jupe)]), - set_prolog_flag(user_output, jupo), - set_prolog_flag(user_error, jupe). - -exit_cell(_Self) :- - close( jupo), - close( jupe). - - -completions(S, Self) :- - open_mem_read_stream(S, St), - scan_to_list(St, Tokens), - close(St), - reverse(Tokens, RTokens), - strip_final_tokens(RTokens, MyTokens), - setof( Completion, complete(MyTokens, Completion), Cs), - Self.completions := Cs. - - -strip_final_tokens(['EOT'|Ts], Ts) :- !. -strip_final_tokens( Ts, Ts ). - -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), - \+ arg( Rest ), - file_or_library( Prefix, C). -complete([C,l,-,'['|More], - isconsult(A), - %B = l, - C=atom(Prefix), - \+ arg( Rest ), - file_or_library( Prefix, C). -complete( [atom(F)|Rest], C) :- - \+ arg( Rest ), - predicate( F, Pred, Arity ), - cont( Arity, F, Pred, C). - -isconsult( atom(use_module) ). -isconsult( atom(ensure_loaded) ). -isconsult( atom(compile) ). -isconsult( atom(consult) ). -isconsult( atom(reconsult) ). -isconsult( atom(load_files) ). -isconsult( '[' ). - -arg([']'|_]). -arg([l|_]). - -file_or_library(F,C) :- - libsym(C0), - atom_cooncat(F,C,Co). -file_or_library(F,C) :- - check_file(F0,C). - -check_file(F0,C) :- - atom_concat('\'',F,F0), - !, - absolute_file_name( F, FF, [access(none)] ), - atom_concat( FF, '*' , Pat), - absolute_file_name( Pat, C0, [glob(true)] ), - atom_concat(Pat,C00,C0), - atom_conct(C00,'\'',C). -check_file(F0,C) :- - atom_concat( F0, '*' , Pat), - absolute_file_name( Pat, C0, [glob(true)] ), - atom_concat(Pat,C,C0). - -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). - -cont(0, F, P, P0):- - atom_concat( F, P, P0 ). -cont( _, F, P, PB ):- - atom_concat( [F, P, '('], PB ). diff --git a/packages/python/yap_kernel/yap_ipython/prolog/jupyter.yap b/packages/python/yap_kernel/yap_ipython/prolog/jupyter.yap index e0f6c39c8..cc276a68b 100644 --- a/packages/python/yap_kernel/yap_ipython/prolog/jupyter.yap +++ b/packages/python/yap_kernel/yap_ipython/prolog/jupyter.yap @@ -35,7 +35,8 @@ completions(S, Self) :- strip_final_tokens(['EOT'|Ts], Ts) :- !. -strip_final_tokens( Ts, Ts ).|_], +strip_final_tokens( Ts, Ts ). + complete([E,l,C,l,A|More], isconsult(A), %B = l, @@ -80,10 +81,10 @@ isconsult( '[' ). arg([']'|_]). arg([l|_]). -fileerrors-or_library(F,C) :- +file_or_library(F,C) :- libsym(C0), atom_cooncat(F,C,Co). -fileerrors-or_library(F,C) :- +file_or_library(F,C) :- check_file(F0,C). check_file(F0,C) :- @@ -117,6 +118,6 @@ predicate(N,P,A) :- atom_concat(N,P,P0). cont(0, F, P, P0)- :- - atom_concat( F, P, PB ). + atom_concat( F, P, P0 ). cont( _, F, P, PB ):- atom_concat( [F, P, '('], PB ).