new jupiter intrface
This commit is contained in:
1
packages/python/swig/yap4py/__main__.py
Normal file
1
packages/python/swig/yap4py/__main__.py
Normal file
@@ -0,0 +1 @@
|
||||
import yap4py.yapi
|
@@ -1,54 +0,0 @@
|
||||
/*
|
||||
%% @file yapi.yap
|
||||
%% @brief support yap shell
|
||||
%%
|
||||
:- module(yapi, [bindvars/2]).
|
||||
|
||||
:- use_module( library(maplist) ).
|
||||
:- use_module( library(rbtrees) ).
|
||||
|
||||
bindvars( [], [] ) :- !.
|
||||
bindvars( L, NL ) :-
|
||||
rb_new(T),
|
||||
% trace,
|
||||
foldl2( bind, L, NL, T, _ , 0, _),
|
||||
term_variables(NL, Vs),
|
||||
foldl( bind_new, Vs, 0, _).
|
||||
|
||||
|
||||
bind(t(_,t(X,Y)), Z, T0, T, N1, N2) :-
|
||||
!,
|
||||
bind(X=Y, Z, T0, T, N1, N2).
|
||||
bind(tuple(_,tuple(X,Y)), Z, T0, T, N1, N2) :-
|
||||
!,
|
||||
bind(X=Y, Z, T0, T, N1, N2).
|
||||
bind(X=Y, X=X, T0, T, N, N) :-
|
||||
var(Y),
|
||||
!,
|
||||
rb_update(T0, Y, X, T).
|
||||
bind(X = G, X = G, T, T, N0, N0) :-
|
||||
ground(G),
|
||||
!.
|
||||
bind(X = C, X = NC, T, NT, N0, NF) :-
|
||||
C =.. [N|L],
|
||||
foldl2(newb, L, NL, T, NT, N0, NF),
|
||||
NC =.. [N|NL].
|
||||
|
||||
newb(Y, X, T, T, N, N) :-
|
||||
var(Y),
|
||||
rb_lookup(Y, X, T),
|
||||
!.
|
||||
newb(Y, X, T, TN, N, NF) :-
|
||||
var(Y),
|
||||
!,
|
||||
rb_insert(Y, T, X, TN),
|
||||
NF is N+1,
|
||||
atomic_concat('_',N,X).
|
||||
newb(Y, Y, T, T, N, N) :-
|
||||
ground(Y),
|
||||
!.
|
||||
newb(Y, X, T, NT, N0, NF) :-
|
||||
Y =.. [N|L],
|
||||
foldl2(newb, L, NL, T, NT, N0, NF),
|
||||
X =.. [N|NL].
|
||||
*/
|
@@ -1,6 +1,7 @@
|
||||
|
||||
import os.path
|
||||
import sys
|
||||
import keyword
|
||||
# debugging support.
|
||||
# import pdb
|
||||
from collections import namedtuple
|
||||
@@ -20,6 +21,8 @@ class Engine( YAPEngine ):
|
||||
YAPEngine.__init__(self,args)
|
||||
self.goal( set_prolog_flag('verbose', 'silent' ) )
|
||||
self.goal( use_module(library('yapi') ) )
|
||||
self.goal( set_prolog_flag('verbose', 'normal' ) )
|
||||
|
||||
|
||||
def run(self, g, m=None):
|
||||
if m:
|
||||
@@ -81,7 +84,16 @@ class PrologTableIter:
|
||||
self.q = None
|
||||
raise StopIteration()
|
||||
|
||||
f2p = []
|
||||
for i in range(16):
|
||||
f2p += [{}]
|
||||
|
||||
def named( name, arity):
|
||||
if arity > 0 and name.isidentifier() and not keyword.iskeyword(name):
|
||||
s = []
|
||||
for i in range(arity):
|
||||
s += ["A" + str(i)]
|
||||
f2p[arity][name] = namedtuple(name, s)
|
||||
|
||||
class PrologPredicate( YAPPrologPredicate ):
|
||||
""" Interface to Prolog Predicate"""
|
||||
@@ -103,8 +115,12 @@ yapi_query = namedtuple( 'yapi_query', 'vars dict')
|
||||
show_answer = namedtuple( 'show_answer', 'vars dict')
|
||||
set_prolog_flag = namedtuple('set_prolog_flag', 'flag new_value')
|
||||
|
||||
def v():
|
||||
return yap.YAPVarTerm()
|
||||
class v(YAPVarTerm):
|
||||
def __init__(self):
|
||||
super().__init__()
|
||||
|
||||
def binding(self):
|
||||
return self.term()
|
||||
|
||||
def numbervars( q ):
|
||||
Dict = {}
|
||||
@@ -113,105 +129,110 @@ def numbervars( q ):
|
||||
return Dict
|
||||
rc = q.namedVarsVector()
|
||||
q.r = q.goal().numbervars()
|
||||
print( rc )
|
||||
o = []
|
||||
for i in rc:
|
||||
if len(i) == 2:
|
||||
do = str(i[0]) + " = " + str( i[1] ) + "\n"
|
||||
o += do
|
||||
print(do)
|
||||
else:
|
||||
do = str(i[0]) + " = " + str( i[1] ) + "\n"
|
||||
o += do
|
||||
print(do)
|
||||
return o
|
||||
|
||||
def answer(q):
|
||||
try:
|
||||
v = q.next()
|
||||
if v:
|
||||
print( bindings )
|
||||
return v
|
||||
except Exception as e:
|
||||
print(e.args[1])
|
||||
return False
|
||||
class YAPShell:
|
||||
|
||||
def query_prolog(engine, s):
|
||||
# import pdb; pdb.set_trace()
|
||||
#
|
||||
# construct a query from a one-line string
|
||||
# q is opaque to Python
|
||||
bindings = {}
|
||||
q = engine.query(python_query(s, bindings))
|
||||
# vs is the list of variables
|
||||
# you can print it out, the left-side is the variable name,
|
||||
# the right side wraps a handle to a variable
|
||||
# pdb.set_trace()
|
||||
# #pdb.set_trace()
|
||||
# atom match either symbols, or if no symbol exists, sttrings, In this case
|
||||
# variable names should match strings
|
||||
#for eq in vs:
|
||||
# if not isinstance(eq[0],str):
|
||||
# print( "Error: Variable Name matches a Python Symbol")
|
||||
# return
|
||||
ask = True
|
||||
# launch the query
|
||||
while answer(q):
|
||||
# deterministic = one solution
|
||||
if q.deterministic():
|
||||
# done
|
||||
q.close()
|
||||
return True, True
|
||||
if ask:
|
||||
s = input("more(;), all(*), no(\\n), python(#) ?").lstrip()
|
||||
if s.startswith(';') or s.startswith('y'):
|
||||
continue
|
||||
elif s.startswith('#'):
|
||||
try:
|
||||
exec(s.lstrip('#'))
|
||||
except:
|
||||
raise
|
||||
elif s.startswith('*') or s.startswith('a'):
|
||||
ask = False
|
||||
continue
|
||||
else:
|
||||
break
|
||||
print("No (more) answers")
|
||||
q.close()
|
||||
return
|
||||
|
||||
def live(**kwargs):
|
||||
loop = True
|
||||
while loop:
|
||||
def answer(self, q):
|
||||
try:
|
||||
s = input("?- ")
|
||||
if not s:
|
||||
loop = False
|
||||
else:
|
||||
query_prolog(engine, s)
|
||||
except SyntaxError as err:
|
||||
print("Syntax Error error: {0}".format(err))
|
||||
except EOFError:
|
||||
return
|
||||
except RuntimeError as err:
|
||||
print("YAP Execution Error: {0}".format(err))
|
||||
except ValueError:
|
||||
print("Could not convert data to an integer.")
|
||||
except:
|
||||
print("Unexpected error:", sys.exc_info()[0])
|
||||
raise
|
||||
engine.close()
|
||||
#
|
||||
# initialize engine
|
||||
# engine = yap.YAPEngine();
|
||||
# engine = yap.YAPEngine(yap.YAPParams());
|
||||
#
|
||||
#
|
||||
self.bindings = {}
|
||||
v = q.next()
|
||||
if v:
|
||||
print( self.bindings )
|
||||
return v
|
||||
except Exception as e:
|
||||
print(e.args[1])
|
||||
return False
|
||||
|
||||
def boot_yap(**kwargs):
|
||||
return Engine(**kwargs)
|
||||
def query_prolog(self, engine, s):
|
||||
# import pdb; pdb.set_trace()
|
||||
#
|
||||
# construct a query from a one-line string
|
||||
# q is opaque to Python
|
||||
#
|
||||
q = engine.query(python_query(self, s))
|
||||
#
|
||||
# # vs is the list of variables
|
||||
# you can print it out, the left-side is the variable name,
|
||||
# the right side wraps a handle to a variable
|
||||
# pdb.set_trace()
|
||||
# #pdb.set_trace()
|
||||
# atom match either symbols, or if no symbol exists, sttrings, In this case
|
||||
# variable names should match strings
|
||||
#for eq in vs:
|
||||
# if not isinstance(eq[0],str):
|
||||
# print( "Error: Variable Name matches a Python Symbol")
|
||||
# return
|
||||
do_ask = True
|
||||
self.port = "call"
|
||||
# launch the query
|
||||
while self.answer(q):
|
||||
if self.port == "exit":
|
||||
# done
|
||||
q.close()
|
||||
return True, True
|
||||
if do_ask:
|
||||
s = input("more(;), all(*), no(\\n), python(#) ?").lstrip()
|
||||
if s.startswith(';') or s.startswith('y'):
|
||||
continue
|
||||
elif s.startswith('#'):
|
||||
try:
|
||||
exec(s.lstrip('#'))
|
||||
except:
|
||||
raise
|
||||
elif s.startswith('*') or s.startswith('a'):
|
||||
do_ask = False
|
||||
continue
|
||||
else:
|
||||
break
|
||||
print("No (more) answers")
|
||||
q.close()
|
||||
return
|
||||
|
||||
def live(self, engine, **kwargs):
|
||||
loop = True
|
||||
while loop:
|
||||
try:
|
||||
s = input("?- ")
|
||||
if not s:
|
||||
loop = False
|
||||
else:
|
||||
self.query_prolog(engine, s)
|
||||
except SyntaxError as err:
|
||||
print("Syntax Error error: {0}".format(err))
|
||||
except EOFError:
|
||||
return
|
||||
except RuntimeError as err:
|
||||
print("YAP Execution Error: {0}".format(err))
|
||||
except ValueError:
|
||||
print("Could not convert data to an integer.")
|
||||
except:
|
||||
print("Unexpected error:", sys.exc_info()[0])
|
||||
raise
|
||||
engine.close()
|
||||
#
|
||||
# initialize engine
|
||||
# engine = yap.YAPEngine();
|
||||
# engine = yap.YAPEngine(yap.YAPParams());
|
||||
#
|
||||
def __init__(self, engine, **kwargs):
|
||||
self.live(engine)
|
||||
|
||||
|
||||
|
||||
def main():
|
||||
engine = Engine()
|
||||
handler = numbervars
|
||||
YAPShell(engine)
|
||||
|
||||
if __name__ == "__main__":
|
||||
engine = boot_yap()
|
||||
handler = numbervars
|
||||
live()
|
||||
main()
|
||||
|
@@ -1,12 +1,19 @@
|
||||
drye%% @file yapi.yap
|
||||
%% @file yapi.yap
|
||||
%% @brief support yap shell
|
||||
%%
|
||||
:- module(yapi, [python_query/2,
|
||||
|
||||
% :- yap_flag(verbose, verbose).
|
||||
|
||||
:- use_module( library(python) ).
|
||||
|
||||
:- module(yapi, [
|
||||
python_ouput/0,
|
||||
show_answer/2,
|
||||
show_answer/3,
|
||||
yap_query/4,
|
||||
yapi_query/2]).
|
||||
python_query/2,
|
||||
yapi_query/2
|
||||
]).
|
||||
|
||||
:- use_module( library(lists) ).
|
||||
:- use_module( library(maplist) ).
|
||||
@@ -14,102 +21,49 @@ drye%% @file yapi.yap
|
||||
:- use_module( library(terms) ).
|
||||
:- use_module( library(python) ).
|
||||
|
||||
|
||||
%% @pred yap_query(sGoal, + VarList, +OutStream, - Dictionary)
|
||||
%% @pred yap_query(0:Goal, + VarList, - Dictionary)
|
||||
%%
|
||||
%% dictionary, Examples
|
||||
%%
|
||||
%%
|
||||
python_query( String, D ) :-
|
||||
atomic_to_term( String, Goal, VarNames ),
|
||||
yap_query( Goal, VarNames, user_error, Dict),
|
||||
D := Dict,
|
||||
yap4py.yapi.bindings := Dict.
|
||||
:- python_import(yap4py.yapi).
|
||||
|
||||
%% @pred yapi_query( + VarList, - Dictionary)
|
||||
%%
|
||||
%% dictionary, Examples
|
||||
%%
|
||||
%%
|
||||
yapi_query( VarNames, Dict ) :-
|
||||
show_answer(VarNames, Dict).
|
||||
yapi_query( VarNames, Self ) :-
|
||||
show_answer(VarNames, Dict),
|
||||
Self.bindings := Dict.
|
||||
|
||||
:- initialization set_preds.
|
||||
|
||||
|
||||
%% @pred yap_query(0:Goal, + VarList, +OutStream, - Dictionary)
|
||||
%% @pred yap_query(0:Goal, + VarList, - Dictionary)
|
||||
%%
|
||||
%% dictionary, Examples
|
||||
%%
|
||||
%%
|
||||
yap_query( Goal, VarNames, Stream, Dictionary) :-
|
||||
(
|
||||
call(Goal)
|
||||
*->
|
||||
!,
|
||||
show_answer(VarNames, Stream, Dictionary)
|
||||
).
|
||||
|
||||
yap_query( VarNames, Dictionary) :-
|
||||
yap_query( VarNames, user_output, Dictionary).
|
||||
|
||||
show_answer(QVs0, Dict) :-
|
||||
show_answer(QVs0, user_error, Dict).
|
||||
|
||||
show_answer(QVs0, Stream, Dict) :-
|
||||
copy_term(QVs0, QVs),
|
||||
copy_term(QVs0, QVs1),
|
||||
rb_new(RB),
|
||||
foldl2(bind_qv, QVs, QVs1, [], LP, {}-RB, Dict-_),
|
||||
!,
|
||||
term_variables(QVs, IVs),
|
||||
term_variables(QVs1, IVs1),
|
||||
foldl( enumerate, IVs, IVs1, 1, _ ),
|
||||
out(LP, Stream ).
|
||||
show_answer(_, _, {}) :-
|
||||
format(' yes.~n', [] ).
|
||||
|
||||
bind_qv(V=V0, V1 = V01, Vs, Vs, Vs1-RB, Vs1-RB) :-
|
||||
var(V0),
|
||||
!,
|
||||
'$VAR'(V) = V0,
|
||||
V1 = V01.
|
||||
% atom_string(V1, V01).
|
||||
bind_qv(V='$VAR'(Vi), V1=S1, Vs, [V='$VAR'(Vi)|Vs], D0-RB, D-RB) :- !,
|
||||
add2dict(D0, V1:S1, D).
|
||||
bind_qv(V=S, V1=S1, Vs, [V=S|Vs], D0-RB0, D-RB0) :-
|
||||
% fix_tree( S, SS, S1, SS1, RB0, RBT),
|
||||
add2dict(D0, V1:S1, D).
|
||||
|
||||
|
||||
add2dict({}, B, {B}).
|
||||
add2dict({C}, B, {B,C}).
|
||||
|
||||
enumerate('$VAR'(A), A, I, I1) :-
|
||||
enum(I, Chars),
|
||||
atom_codes(A,[0'_|Chars]),
|
||||
I1 is I + 1.
|
||||
|
||||
enum(I, [C]) :-
|
||||
I < 26,
|
||||
!,
|
||||
C is "A" + I.
|
||||
enum(I, [C|Cs]) :-
|
||||
J is I//26,
|
||||
K is I mod 26,
|
||||
C is "A" +K,
|
||||
enum(J, Cs).
|
||||
|
||||
out(Bs, S) :-
|
||||
output(Bs, S),
|
||||
!.
|
||||
out([_|Bs], S) :-
|
||||
out(Bs, S).
|
||||
|
||||
output([V=B], S) :-
|
||||
!,
|
||||
format(S, '~a = ~q~n', [V, B]).
|
||||
output([V=B|_Ns], S) :-
|
||||
format( S, '~a = ~q.~n', [V, B]),
|
||||
set_preds :-
|
||||
current_predicate(P, Q),
|
||||
functor(Q,P,A),
|
||||
atom_string(P,S),
|
||||
:= yap4py.yapi.named( S, A),
|
||||
fail.
|
||||
set_preds :-
|
||||
system_predicate(P/A),
|
||||
atom_string(P,S),
|
||||
:= yap4py.yapi.named( S, A),
|
||||
fail.
|
||||
set_preds.
|
||||
|
||||
argi(N,I,I1) :-
|
||||
atomic_concat(`A`,I,N),
|
||||
I1 is I+1.
|
||||
|
||||
python_query( Self, String ) :-
|
||||
yap_flag(typein_module, Mod),
|
||||
atomic_to_term( String, Goal, VarNames ),
|
||||
query_to_answer( Mod:Goal, VarNames, Status, Bindings),
|
||||
maplist(in_dict(Self.bindings), Bindings),
|
||||
write_query_answer( Bindings ),
|
||||
nl( user_error ),
|
||||
Self.port := Status.
|
||||
|
||||
in_dict(Dict, var([V0,V|Vs])) :- !,
|
||||
Dict[V] := V0,
|
||||
in_dict( Dict, var([V0|Vs])).
|
||||
in_dict(Dict, nonvar([V0|Vs],G)) :- !,
|
||||
Dict[V0] := G,
|
||||
in_dict( Dict, var([V0|Vs])).
|
||||
in_dict(_, _).
|
||||
|
Reference in New Issue
Block a user