more progress
This commit is contained in:
parent
6e3f01e0b3
commit
e529e79582
@ -53,6 +53,8 @@
|
|||||||
:- use_module(library(lists),
|
:- use_module(library(lists),
|
||||||
[reverse/2]).
|
[reverse/2]).
|
||||||
|
|
||||||
|
:- use_module(library(maplist)).
|
||||||
|
|
||||||
:- use_module(library('clpbn/aggregates'),
|
:- use_module(library('clpbn/aggregates'),
|
||||||
[check_for_agg_vars/2]).
|
[check_for_agg_vars/2]).
|
||||||
|
|
||||||
@ -87,33 +89,29 @@
|
|||||||
jt([[]],_,_) :- !.
|
jt([[]],_,_) :- !.
|
||||||
jt(LLVs,Vs0,AllDiffs) :-
|
jt(LLVs,Vs0,AllDiffs) :-
|
||||||
init_jt_solver(LLVs, Vs0, AllDiffs, State),
|
init_jt_solver(LLVs, Vs0, AllDiffs, State),
|
||||||
run_jt_solver(LLVs, LLPs, State),
|
maplist(run_jt_solver, LLVs, LLPs, State),
|
||||||
clpbn_bind_vals(LLVs,LLPs,AllDiffs).
|
clpbn_bind_vals(LLVs,LLPs,AllDiffs).
|
||||||
|
|
||||||
|
|
||||||
init_jt_solver(LLVs, Vs0, _, State) :-
|
init_jt_solver(LLVs, Vs0, _, State) :-
|
||||||
check_for_agg_vars(Vs0, Vs1),
|
check_for_agg_vars(Vs0, Vs1),
|
||||||
init_influences(Vs1, G, RG),
|
init_influences(Vs1, G, RG),
|
||||||
init_jt_solver_for_questions(LLVs, G, RG, State).
|
maplist(init_jt_solver_for_question(G, RG), LLVs, State).
|
||||||
|
|
||||||
init_jt_solver_for_questions([], _, _, []).
|
init_jt_solver_for_question(G, RG, LLVs, state(JTree, Evidence)) :-
|
||||||
init_jt_solver_for_questions([LLVs|MoreLLVs], G, RG, [state(JTree, Evidence)|State]) :-
|
|
||||||
influences(LLVs, G, RG, NVs0),
|
influences(LLVs, G, RG, NVs0),
|
||||||
sort(NVs0, NVs),
|
sort(NVs0, NVs),
|
||||||
get_graph(NVs, BayesNet, CPTs, Evidence),
|
get_graph(NVs, BayesNet, CPTs, Evidence),
|
||||||
build_jt(BayesNet, CPTs, JTree),
|
build_jt(BayesNet, CPTs, JTree).
|
||||||
init_jt_solver_for_questions(MoreLLVs, G, RG, State).
|
|
||||||
|
|
||||||
run_jt_solver([], [], []).
|
run_jt_solver(LVs, LPs, state(JTree, Evidence)) :-
|
||||||
run_jt_solver([LVs|MoreLVs], [LPs|MorePs], [state(JTree, Evidence)|MoreState]) :-
|
|
||||||
% JTree is a dgraph
|
% JTree is a dgraph
|
||||||
% now our tree has cpts
|
% now our tree has cpts
|
||||||
fill_with_cpts(JTree, NewTree),
|
fill_with_cpts(JTree, NewTree),
|
||||||
% write_tree(NewTree,0),
|
% write_tree(0, NewTree),
|
||||||
propagate_evidence(Evidence, NewTree, EvTree),
|
propagate_evidence(Evidence, NewTree, EvTree),
|
||||||
message_passing(EvTree, MTree),
|
message_passing(EvTree, MTree),
|
||||||
get_margin(MTree, LVs, LPs),
|
get_margin(MTree, LVs, LPs).
|
||||||
run_jt_solver(MoreLVs, MorePs, MoreState).
|
|
||||||
|
|
||||||
get_graph(LVs, BayesNet, CPTs, Evidence) :-
|
get_graph(LVs, BayesNet, CPTs, Evidence) :-
|
||||||
run_vars(LVs, Edges, Vertices, CPTs, Evidence),
|
run_vars(LVs, Edges, Vertices, CPTs, Evidence),
|
||||||
@ -510,16 +508,16 @@ find_clique_from_kids([_|Kids], LVs, Clique, Dist) :-
|
|||||||
find_clique_from_kids(Kids, LVs, Clique, Dist).
|
find_clique_from_kids(Kids, LVs, Clique, Dist).
|
||||||
|
|
||||||
|
|
||||||
write_tree(tree(Clique-(Dist,_),Leaves), I0) :- !,
|
write_tree(I0, tree(Clique-(Dist,_),Leaves)) :- !,
|
||||||
matrix:matrix_to_list(Dist,L),
|
matrix:matrix_to_list(Dist,L),
|
||||||
format('~*c ~w:~w~n',[I0,0' ,Clique,L]),
|
format('~*c ~w:~w~n',[I0,0' ,Clique,L]),
|
||||||
I is I0+2,
|
I is I0+2,
|
||||||
write_subtree(Leaves, I).
|
maplist(write_tree(I), Leaves).
|
||||||
write_tree(tree(Clique-Dist,Leaves), I0) :-
|
write_tree(I0, tree(Clique-Dist,Leaves), I0) :-
|
||||||
matrix:matrix_to_list(Dist,L),
|
matrix:matrix_to_list(Dist,L),
|
||||||
format('~*c ~w:~w~n',[I0,0' ,Clique, L]),
|
format('~*c ~w:~w~n',[I0,0' ,Clique, L]),
|
||||||
I is I0+2,
|
I is I0+2,
|
||||||
write_subtree(Leaves, I).
|
maplist(write_tree(I), Leaves).
|
||||||
|
|
||||||
write_subtree([], _).
|
write_subtree([], _).
|
||||||
write_subtree([Tree|Leaves], I) :-
|
write_subtree([Tree|Leaves], I) :-
|
||||||
|
@ -18,12 +18,12 @@ data(t,t,_,f).
|
|||||||
data(t,f,f,t).
|
data(t,f,f,t).
|
||||||
data(t,f,t,t).
|
data(t,f,t,t).
|
||||||
|
|
||||||
%:- clpbn:set_clpbn_flag(em_solver,gibbs).
|
%:- set_pfl_flag(em_solver,gibbs).
|
||||||
%:- clpbn:set_clpbn_flag(em_solver,jt).
|
%:- set_pfl_flag(em_solver,jt).
|
||||||
:- clpbn:set_clpbn_flag(em_solver,hve).
|
:- set_pfl_flag(em_solver,hve).
|
||||||
:- clpbn:set_clpbn_flag(em_solver,bdd).
|
%:- set_pfl_flag(em_solver,bp).
|
||||||
%:- clpbn:set_clpbn_flag(em_solver,bp).
|
:- set_pfl_flag(em_solver,ve).
|
||||||
%:- clpbn:set_clpbn_flag(em_solver,ve).
|
:- set_pfl_flag(em_solver,bdd).
|
||||||
|
|
||||||
timed_main :-
|
timed_main :-
|
||||||
statistics(runtime, _),
|
statistics(runtime, _),
|
||||||
|
@ -52,7 +52,7 @@ set_bdd_from_list(T0, VS, Manager, Cudd) :-
|
|||||||
numbervars(VS,0,_),
|
numbervars(VS,0,_),
|
||||||
generate_releases(T0, Manager, T),
|
generate_releases(T0, Manager, T),
|
||||||
% T0 = T,
|
% T0 = T,
|
||||||
% writeln_list(T),
|
% writeln_list(T0),
|
||||||
list_to_cudd(T,Manager,_Cudd0,Cudd).
|
list_to_cudd(T,Manager,_Cudd0,Cudd).
|
||||||
|
|
||||||
generate_releases(T0, Manager, T) :-
|
generate_releases(T0, Manager, T) :-
|
||||||
@ -82,31 +82,31 @@ writeln_list(B.Bindings) :-
|
|||||||
|
|
||||||
%list_to_cudd(H._List,_Manager,_Cudd0,_CuddF) :- writeln(l:H), fail.
|
%list_to_cudd(H._List,_Manager,_Cudd0,_CuddF) :- writeln(l:H), fail.
|
||||||
list_to_cudd([],_Manager,Cudd,Cudd) :- writeln('X').
|
list_to_cudd([],_Manager,Cudd,Cudd) :- writeln('X').
|
||||||
list_to_cudd(release_node(M,cudd(V)).T, Manager, Cudd0, CuddF) :- !,
|
list_to_cudd([release_node(M,cudd(V))|T], Manager, Cudd0, CuddF) :- !,
|
||||||
write('-'), flush_output,
|
write('-'), flush_output,
|
||||||
cudd_release_node(M,V),
|
cudd_release_node(M,V),
|
||||||
list_to_cudd(T, Manager, Cudd0, CuddF).
|
list_to_cudd(T, Manager, Cudd0, CuddF).
|
||||||
list_to_cudd((V=0*_Par).T, Manager, _Cudd0, CuddF) :- !,
|
list_to_cudd([(V=0*_Par)|T], Manager, _Cudd0, CuddF) :- !,
|
||||||
write('0'), flush_output,
|
write('0'), flush_output,
|
||||||
term_to_cudd(0, Manager, Cudd),
|
term_to_cudd(0, Manager, Cudd),
|
||||||
V = cudd(Cudd),
|
V = cudd(Cudd),
|
||||||
list_to_cudd(T, Manager, Cudd, CuddF).
|
list_to_cudd(T, Manager, Cudd, CuddF).
|
||||||
list_to_cudd((V=0).T, Manager, _Cudd0, CuddF) :- !,
|
list_to_cudd([(V=0)|T], Manager, _Cudd0, CuddF) :- !,
|
||||||
write('0'), flush_output,
|
write('0'), flush_output,
|
||||||
term_to_cudd(0, Manager, Cudd),
|
term_to_cudd(0, Manager, Cudd),
|
||||||
V = cudd(Cudd),
|
V = cudd(Cudd),
|
||||||
list_to_cudd(T, Manager, Cudd, CuddF).
|
list_to_cudd(T, Manager, Cudd, CuddF).
|
||||||
list_to_cudd((V=_Tree*0).T, Manager, _Cudd0, CuddF) :- !,
|
list_to_cudd([(V=_Tree*0)|T], Manager, _Cudd0, CuddF) :- !,
|
||||||
write('0'), flush_output,
|
write('0'), flush_output,
|
||||||
term_to_cudd(0, Manager, Cudd),
|
term_to_cudd(0, Manager, Cudd),
|
||||||
V = cudd(Cudd),
|
V = cudd(Cudd),
|
||||||
list_to_cudd(T, Manager, Cudd, CuddF).
|
list_to_cudd(T, Manager, Cudd, CuddF).
|
||||||
list_to_cudd((V=Tree*1).T, Manager, _Cudd0, CuddF) :- !,
|
list_to_cudd([(V=Tree*1)|T], Manager, _Cudd0, CuddF) :- !,
|
||||||
write('.'), flush_output,
|
write('.'), flush_output,
|
||||||
term_to_cudd(Tree, Manager, Cudd),
|
term_to_cudd(Tree, Manager, Cudd),
|
||||||
V = cudd(Cudd),
|
V = cudd(Cudd),
|
||||||
list_to_cudd(T, Manager, Cudd, CuddF).
|
list_to_cudd(T, Manager, Cudd, CuddF).
|
||||||
list_to_cudd((V=Tree).T, Manager, _Cudd0, CuddF) :-
|
list_to_cudd([(V=Tree)|T], Manager, _Cudd0, CuddF) :-
|
||||||
write('.'), flush_output,
|
write('.'), flush_output,
|
||||||
( ground(Tree) -> true ; throw(error(instantiation_error(Tree))) ),
|
( ground(Tree) -> true ; throw(error(instantiation_error(Tree))) ),
|
||||||
term_to_cudd(Tree, Manager, Cudd),
|
term_to_cudd(Tree, Manager, Cudd),
|
||||||
|
@ -1 +1 @@
|
|||||||
Subproject commit 6dd05cb45b22cc38e3467d0264706f61381c8945
|
Subproject commit be76ebc1f9544a5ee96f9f94bebf58252b3a938c
|
@ -1 +1 @@
|
|||||||
Subproject commit 2a596b7cce313c2702f275a189c1ea6a67a20f84
|
Subproject commit 32554931ed7a59771bf1939cfad434c253b459e2
|
17
packages/python/examples/pyx.pl
Normal file
17
packages/python/examples/pyx.pl
Normal file
@ -0,0 +1,17 @@
|
|||||||
|
|
||||||
|
:- use_module(library(python)).
|
||||||
|
|
||||||
|
:- initialization(main).
|
||||||
|
|
||||||
|
main :-
|
||||||
|
ex(X),
|
||||||
|
flush_output,
|
||||||
|
fail.
|
||||||
|
main.
|
||||||
|
|
||||||
|
ex(hello_world) :-
|
||||||
|
c = pyx:canvas:canvas,
|
||||||
|
:= c:text(0, 0, 'Hello, world!'),
|
||||||
|
:= c:stroke(path:line(0, 0, 2, 0)),
|
||||||
|
c.writePDFfile('hello.pdf').
|
||||||
|
|
@ -112,7 +112,7 @@ ex(slices) :-
|
|||||||
|
|
||||||
ex(lists) :-
|
ex(lists) :-
|
||||||
a := [66.25, 333, 333, 1, 1234.5],
|
a := [66.25, 333, 333, 1, 1234.5],
|
||||||
A1 := $a:count(333), A2 := $a:count(66.25), A3 := $a:count('x'),
|
A1 := $a:count(333), A2 := $a:count(66.25), A3 := $a:count(x),
|
||||||
format('counts=~d ~d ~d~n',[A1,A2,A3]),
|
format('counts=~d ~d ~d~n',[A1,A2,A3]),
|
||||||
:= $a:insert(2, -1),
|
:= $a:insert(2, -1),
|
||||||
:= $a:append(333),
|
:= $a:append(333),
|
||||||
@ -129,3 +129,26 @@ ex(lists) :-
|
|||||||
D := $a,
|
D := $a,
|
||||||
format('a=~w~n', [D]).
|
format('a=~w~n', [D]).
|
||||||
|
|
||||||
|
ex(iter) :-
|
||||||
|
it := iter(abc),
|
||||||
|
format('iter= ', []),
|
||||||
|
iterate(iter).
|
||||||
|
|
||||||
|
iterate(iter) :-
|
||||||
|
repeat,
|
||||||
|
( X1 := $it:next,
|
||||||
|
format('i ~a~n', [X1])
|
||||||
|
->
|
||||||
|
fail
|
||||||
|
;
|
||||||
|
!
|
||||||
|
).
|
||||||
|
|
||||||
|
ex(range) :-
|
||||||
|
r1 := range(1000),
|
||||||
|
r2 := range(1000,2000),
|
||||||
|
r3 := range(2000,10000,1),
|
||||||
|
S := sum($r1+ $r2+ $r3),
|
||||||
|
format('range=~d~n', [S]).
|
||||||
|
|
||||||
|
|
||||||
|
@ -19,11 +19,16 @@ static functor_t FUNCTOR_dollar1,
|
|||||||
FUNCTOR_dir1,
|
FUNCTOR_dir1,
|
||||||
FUNCTOR_float1,
|
FUNCTOR_float1,
|
||||||
FUNCTOR_int1,
|
FUNCTOR_int1,
|
||||||
|
FUNCTOR_iter1,
|
||||||
|
FUNCTOR_iter2,
|
||||||
FUNCTOR_long1,
|
FUNCTOR_long1,
|
||||||
FUNCTOR_iter1,
|
|
||||||
FUNCTOR_len1,
|
FUNCTOR_len1,
|
||||||
FUNCTOR_curly1,
|
FUNCTOR_curly1,
|
||||||
FUNCTOR_ord1,
|
FUNCTOR_ord1,
|
||||||
|
FUNCTOR_range1,
|
||||||
|
FUNCTOR_range2,
|
||||||
|
FUNCTOR_range3,
|
||||||
|
FUNCTOR_sum1,
|
||||||
FUNCTOR_pointer1,
|
FUNCTOR_pointer1,
|
||||||
FUNCTOR_complex2,
|
FUNCTOR_complex2,
|
||||||
FUNCTOR_plus2,
|
FUNCTOR_plus2,
|
||||||
@ -249,6 +254,18 @@ bip_long(term_t t)
|
|||||||
return o;
|
return o;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
static PyObject *
|
||||||
|
bip_iter(term_t t)
|
||||||
|
{
|
||||||
|
PyObject *v;
|
||||||
|
|
||||||
|
if (! PL_get_arg(1, t, t) )
|
||||||
|
return NULL;
|
||||||
|
v = term_to_python(t);
|
||||||
|
return PyObject_GetIter(v);
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
static PyObject *
|
static PyObject *
|
||||||
bip_ord(term_t t)
|
bip_ord(term_t t)
|
||||||
{
|
{
|
||||||
@ -281,6 +298,254 @@ bip_ord(term_t t)
|
|||||||
return NULL;
|
return NULL;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
static PyObject*
|
||||||
|
bip_sum(term_t t)
|
||||||
|
{
|
||||||
|
PyObject *seq;
|
||||||
|
PyObject *result = NULL;
|
||||||
|
PyObject *temp, *item, *iter;
|
||||||
|
|
||||||
|
if (! PL_get_arg(1, t, t) )
|
||||||
|
return NULL;
|
||||||
|
seq = term_to_python(t);
|
||||||
|
iter = PyObject_GetIter(seq);
|
||||||
|
if (iter == NULL)
|
||||||
|
return NULL;
|
||||||
|
|
||||||
|
if (result == NULL) {
|
||||||
|
result = PyInt_FromLong(0);
|
||||||
|
if (result == NULL) {
|
||||||
|
Py_DECREF(iter);
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
} else {
|
||||||
|
/* reject string values for 'start' parameter */
|
||||||
|
if (PyObject_TypeCheck(result, &PyBaseString_Type)) {
|
||||||
|
PyErr_SetString(PyExc_TypeError,
|
||||||
|
"sum() can't sum strings [use ''.join(seq) instead]");
|
||||||
|
Py_DECREF(iter);
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
Py_INCREF(result);
|
||||||
|
}
|
||||||
|
|
||||||
|
#ifndef SLOW_SUM
|
||||||
|
/* Fast addition by keeping temporary sums in C instead of new Python objects.
|
||||||
|
Assumes all inputs are the same type. If the assumption fails, default
|
||||||
|
to the more general routine.
|
||||||
|
*/
|
||||||
|
if (PyInt_CheckExact(result)) {
|
||||||
|
long i_result = PyInt_AS_LONG(result);
|
||||||
|
Py_DECREF(result);
|
||||||
|
result = NULL;
|
||||||
|
while(result == NULL) {
|
||||||
|
item = PyIter_Next(iter);
|
||||||
|
if (item == NULL) {
|
||||||
|
Py_DECREF(iter);
|
||||||
|
if (PyErr_Occurred())
|
||||||
|
return NULL;
|
||||||
|
return PyInt_FromLong(i_result);
|
||||||
|
}
|
||||||
|
if (PyInt_CheckExact(item)) {
|
||||||
|
long b = PyInt_AS_LONG(item);
|
||||||
|
long x = i_result + b;
|
||||||
|
if ((x^i_result) >= 0 || (x^b) >= 0) {
|
||||||
|
i_result = x;
|
||||||
|
Py_DECREF(item);
|
||||||
|
continue;
|
||||||
|
}
|
||||||
|
}
|
||||||
|
/* Either overflowed or is not an int. Restore real objects and process normally */
|
||||||
|
result = PyInt_FromLong(i_result);
|
||||||
|
temp = PyNumber_Add(result, item);
|
||||||
|
Py_DECREF(result);
|
||||||
|
Py_DECREF(item);
|
||||||
|
result = temp;
|
||||||
|
if (result == NULL) {
|
||||||
|
Py_DECREF(iter);
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
|
if (PyFloat_CheckExact(result)) {
|
||||||
|
double f_result = PyFloat_AS_DOUBLE(result);
|
||||||
|
Py_DECREF(result);
|
||||||
|
result = NULL;
|
||||||
|
while(result == NULL) {
|
||||||
|
item = PyIter_Next(iter);
|
||||||
|
if (item == NULL) {
|
||||||
|
Py_DECREF(iter);
|
||||||
|
if (PyErr_Occurred())
|
||||||
|
return NULL;
|
||||||
|
return PyFloat_FromDouble(f_result);
|
||||||
|
}
|
||||||
|
if (PyFloat_CheckExact(item)) {
|
||||||
|
PyFPE_START_PROTECT("add", Py_DECREF(item); Py_DECREF(iter); return 0)
|
||||||
|
f_result += PyFloat_AS_DOUBLE(item);
|
||||||
|
PyFPE_END_PROTECT(f_result)
|
||||||
|
Py_DECREF(item);
|
||||||
|
continue;
|
||||||
|
}
|
||||||
|
if (PyInt_CheckExact(item)) {
|
||||||
|
PyFPE_START_PROTECT("add", Py_DECREF(item); Py_DECREF(iter); return 0)
|
||||||
|
f_result += (double)PyInt_AS_LONG(item);
|
||||||
|
PyFPE_END_PROTECT(f_result)
|
||||||
|
Py_DECREF(item);
|
||||||
|
continue;
|
||||||
|
}
|
||||||
|
result = PyFloat_FromDouble(f_result);
|
||||||
|
temp = PyNumber_Add(result, item);
|
||||||
|
Py_DECREF(result);
|
||||||
|
Py_DECREF(item);
|
||||||
|
result = temp;
|
||||||
|
if (result == NULL) {
|
||||||
|
Py_DECREF(iter);
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
}
|
||||||
|
}
|
||||||
|
#endif
|
||||||
|
|
||||||
|
for(;;) {
|
||||||
|
item = PyIter_Next(iter);
|
||||||
|
if (item == NULL) {
|
||||||
|
/* error, or end-of-sequence */
|
||||||
|
if (PyErr_Occurred()) {
|
||||||
|
Py_DECREF(result);
|
||||||
|
result = NULL;
|
||||||
|
}
|
||||||
|
break;
|
||||||
|
}
|
||||||
|
/* It's tempting to use PyNumber_InPlaceAdd instead of
|
||||||
|
PyNumber_Add here, to avoid quadratic running time
|
||||||
|
when doing 'sum(list_of_lists, [])'. However, this
|
||||||
|
would produce a change in behaviour: a snippet like
|
||||||
|
|
||||||
|
empty = []
|
||||||
|
sum([[x] for x in range(10)], empty)
|
||||||
|
|
||||||
|
would change the value of empty. */
|
||||||
|
temp = PyNumber_Add(result, item);
|
||||||
|
Py_DECREF(result);
|
||||||
|
Py_DECREF(item);
|
||||||
|
result = temp;
|
||||||
|
if (result == NULL)
|
||||||
|
break;
|
||||||
|
}
|
||||||
|
Py_DECREF(iter);
|
||||||
|
return result;
|
||||||
|
}
|
||||||
|
|
||||||
|
static long
|
||||||
|
get_int(term_t arg)
|
||||||
|
{
|
||||||
|
long ilow;
|
||||||
|
|
||||||
|
if (!PL_get_long(arg, &ilow)) {
|
||||||
|
PyObject *low = term_to_python(arg);
|
||||||
|
if (PyLong_Check(low)) {
|
||||||
|
return PyLong_AsLong(low);
|
||||||
|
} else if (PyInt_Check(low)) {
|
||||||
|
return PyInt_AsLong(low);
|
||||||
|
} else {
|
||||||
|
return 0;
|
||||||
|
}
|
||||||
|
}
|
||||||
|
return ilow;
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
|
/* Return number of items in range/xrange (lo, hi, step). step > 0
|
||||||
|
* required. Return a value < 0 if & only if the true value is too
|
||||||
|
* large to fit in a signed long.
|
||||||
|
*/
|
||||||
|
static long
|
||||||
|
get_len_of_range(long lo, long hi, long step)
|
||||||
|
{
|
||||||
|
/* -------------------------------------------------------------
|
||||||
|
If lo >= hi, the range is empty.
|
||||||
|
Else if n values are in the range, the last one is
|
||||||
|
lo + (n-1)*step, which must be <= hi-1. Rearranging,
|
||||||
|
n <= (hi - lo - 1)/step + 1, so taking the floor of the RHS gives
|
||||||
|
the proper value. Since lo < hi in this case, hi-lo-1 >= 0, so
|
||||||
|
the RHS is non-negative and so truncation is the same as the
|
||||||
|
floor. Letting M be the largest positive long, the worst case
|
||||||
|
for the RHS numerator is hi=M, lo=-M-1, and then
|
||||||
|
hi-lo-1 = M-(-M-1)-1 = 2*M. Therefore unsigned long has enough
|
||||||
|
precision to compute the RHS exactly.
|
||||||
|
---------------------------------------------------------------*/
|
||||||
|
long n = 0;
|
||||||
|
if (lo < hi) {
|
||||||
|
unsigned long uhi = (unsigned long)hi;
|
||||||
|
unsigned long ulo = (unsigned long)lo;
|
||||||
|
unsigned long diff = uhi - ulo - 1;
|
||||||
|
n = (long)(diff / (unsigned long)step + 1);
|
||||||
|
}
|
||||||
|
return n;
|
||||||
|
}
|
||||||
|
|
||||||
|
static PyObject *
|
||||||
|
bip_range(term_t t)
|
||||||
|
{
|
||||||
|
long ilow = 0, ihigh = 0, istep = 1;
|
||||||
|
long bign;
|
||||||
|
Py_ssize_t i, n;
|
||||||
|
int arity;
|
||||||
|
atom_t name;
|
||||||
|
term_t arg = PL_new_term_ref();
|
||||||
|
|
||||||
|
PyObject *v;
|
||||||
|
|
||||||
|
if (!PL_get_name_arity(t, &name, &arity) )
|
||||||
|
return NULL;
|
||||||
|
if (! PL_get_arg(1, t, arg) )
|
||||||
|
return NULL;
|
||||||
|
ilow = get_int(arg);
|
||||||
|
if (arity == 1) {
|
||||||
|
ihigh = ilow;
|
||||||
|
ilow = 0;
|
||||||
|
} else {
|
||||||
|
if (! PL_get_arg(2, t, arg) )
|
||||||
|
return NULL;
|
||||||
|
ihigh = get_int(arg);
|
||||||
|
if (arity == 3) {
|
||||||
|
if (! PL_get_arg(3, t, arg) )
|
||||||
|
return NULL;
|
||||||
|
istep = get_int(arg);
|
||||||
|
}
|
||||||
|
}
|
||||||
|
if (istep == 0) {
|
||||||
|
PyErr_SetString(PyExc_ValueError,
|
||||||
|
"range() step argument must not be zero");
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
if (istep > 0)
|
||||||
|
bign = get_len_of_range(ilow, ihigh, istep);
|
||||||
|
else
|
||||||
|
bign = get_len_of_range(ihigh, ilow, -istep);
|
||||||
|
n = (Py_ssize_t)bign;
|
||||||
|
if (bign < 0 || (long)n != bign) {
|
||||||
|
PyErr_SetString(PyExc_OverflowError,
|
||||||
|
"range() result has too many items");
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
v = PyList_New(n);
|
||||||
|
if (v == NULL)
|
||||||
|
return NULL;
|
||||||
|
for (i = 0; i < n; i++) {
|
||||||
|
PyObject *w = PyInt_FromLong(ilow);
|
||||||
|
if (w == NULL) {
|
||||||
|
Py_DECREF(v);
|
||||||
|
return NULL;
|
||||||
|
}
|
||||||
|
PyList_SET_ITEM(v, i, w);
|
||||||
|
ilow += istep;
|
||||||
|
}
|
||||||
|
return v;
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
static PyObject *
|
static PyObject *
|
||||||
term_to_python(term_t t)
|
term_to_python(term_t t)
|
||||||
{
|
{
|
||||||
@ -400,6 +665,14 @@ term_to_python(term_t t)
|
|||||||
return bip_long(t);
|
return bip_long(t);
|
||||||
} else if (fun == FUNCTOR_float1) {
|
} else if (fun == FUNCTOR_float1) {
|
||||||
return bip_float(t);
|
return bip_float(t);
|
||||||
|
} else if (fun == FUNCTOR_iter1) {
|
||||||
|
return bip_iter(t);
|
||||||
|
} else if (fun == FUNCTOR_range1 ||
|
||||||
|
fun == FUNCTOR_range2 ||
|
||||||
|
fun == FUNCTOR_range3) {
|
||||||
|
return bip_range(t);
|
||||||
|
} else if (fun == FUNCTOR_sum1) {
|
||||||
|
return bip_sum(t);
|
||||||
} else if (fun == FUNCTOR_len1) {
|
} else if (fun == FUNCTOR_len1) {
|
||||||
term_t targ = PL_new_term_ref();
|
term_t targ = PL_new_term_ref();
|
||||||
PyObject *ptr;
|
PyObject *ptr;
|
||||||
@ -416,14 +689,6 @@ term_to_python(term_t t)
|
|||||||
return NULL;
|
return NULL;
|
||||||
ptr = term_to_python(targ);
|
ptr = term_to_python(targ);
|
||||||
return PyObject_Dir(ptr);
|
return PyObject_Dir(ptr);
|
||||||
} else if (fun == FUNCTOR_iter1) {
|
|
||||||
term_t targ = PL_new_term_ref();
|
|
||||||
PyObject *ptr;
|
|
||||||
|
|
||||||
if (! PL_get_arg(1, t, targ) )
|
|
||||||
return NULL;
|
|
||||||
ptr = term_to_python(targ);
|
|
||||||
return PyObject_GetIter(ptr);
|
|
||||||
} else if (fun == FUNCTOR_complex2) {
|
} else if (fun == FUNCTOR_complex2) {
|
||||||
term_t targ = PL_new_term_ref();
|
term_t targ = PL_new_term_ref();
|
||||||
PyObject *lhs, *rhs;
|
PyObject *lhs, *rhs;
|
||||||
@ -1051,6 +1316,8 @@ python_access(term_t obj, term_t f, term_t out)
|
|||||||
if ( PyCallable_Check(pValue) )
|
if ( PyCallable_Check(pValue) )
|
||||||
pValue = PyObject_CallObject(pValue, NULL);
|
pValue = PyObject_CallObject(pValue, NULL);
|
||||||
PyErr_Print();
|
PyErr_Print();
|
||||||
|
if (!pValue)
|
||||||
|
return FALSE;
|
||||||
return python_to_term(pValue, out);
|
return python_to_term(pValue, out);
|
||||||
}
|
}
|
||||||
if (! PL_get_name_arity( f, &name, &arity) ) {
|
if (! PL_get_name_arity( f, &name, &arity) ) {
|
||||||
@ -1156,7 +1423,12 @@ install_python(void)
|
|||||||
FUNCTOR_pointer1 = PL_new_functor(PL_new_atom("__obj__"), 1);
|
FUNCTOR_pointer1 = PL_new_functor(PL_new_atom("__obj__"), 1);
|
||||||
FUNCTOR_dir1 = PL_new_functor(PL_new_atom("dir"), 1);
|
FUNCTOR_dir1 = PL_new_functor(PL_new_atom("dir"), 1);
|
||||||
FUNCTOR_iter1 = PL_new_functor(PL_new_atom("iter"), 1);
|
FUNCTOR_iter1 = PL_new_functor(PL_new_atom("iter"), 1);
|
||||||
|
FUNCTOR_iter2 = PL_new_functor(PL_new_atom("iter"), 2);
|
||||||
FUNCTOR_len1 = PL_new_functor(PL_new_atom("len"), 1);
|
FUNCTOR_len1 = PL_new_functor(PL_new_atom("len"), 1);
|
||||||
|
FUNCTOR_range1 = PL_new_functor(PL_new_atom("range"), 1);
|
||||||
|
FUNCTOR_range2 = PL_new_functor(PL_new_atom("range"), 2);
|
||||||
|
FUNCTOR_range3 = PL_new_functor(PL_new_atom("range"), 3);
|
||||||
|
FUNCTOR_sum1 = PL_new_functor(PL_new_atom("sum"), 1);
|
||||||
FUNCTOR_complex2 = PL_new_functor(PL_new_atom("complex"), 2);
|
FUNCTOR_complex2 = PL_new_functor(PL_new_atom("complex"), 2);
|
||||||
FUNCTOR_plus2 = PL_new_functor(PL_new_atom("+"), 2);
|
FUNCTOR_plus2 = PL_new_functor(PL_new_atom("+"), 2);
|
||||||
FUNCTOR_sub2 = PL_new_functor(PL_new_atom("-"), 2);
|
FUNCTOR_sub2 = PL_new_functor(PL_new_atom("-"), 2);
|
||||||
|
@ -95,21 +95,23 @@ module_extend(M, E, M, E, MRef, MRef).
|
|||||||
python_eval_term(Expression, O) :-
|
python_eval_term(Expression, O) :-
|
||||||
fetch_module(Expression, Module, Exp, MRef), !,
|
fetch_module(Expression, Module, Exp, MRef), !,
|
||||||
(
|
(
|
||||||
atom(Exp)
|
% avoid looking at : as field of module.
|
||||||
->
|
Exp = Obj:Field
|
||||||
python_access(MRef, Exp, O)
|
->
|
||||||
;
|
|
||||||
Exp = Obj:Method
|
|
||||||
->
|
|
||||||
python_access(MRef, Exp, O)
|
python_access(MRef, Exp, O)
|
||||||
;
|
;
|
||||||
functor(Exp, F, _),
|
functor(Exp, F, _),
|
||||||
python_f(MRef, F, FRef),
|
python_f(MRef, F, FRef),
|
||||||
python_check_args(FRef, Exp, NExp),
|
python_check_args(FRef, Exp, NExp)
|
||||||
|
->
|
||||||
python_apply(FRef, NExp, O)
|
python_apply(FRef, NExp, O)
|
||||||
|
;
|
||||||
|
python_access(MRef, Exp, O)
|
||||||
).
|
).
|
||||||
python_eval_term(Obj:Field, O) :-
|
python_eval_term(Obj:Field, O) :- !,
|
||||||
python_access(Obj, Field, O).
|
python_access(Obj, Field, O).
|
||||||
|
python_eval_term(Obj, O) :-
|
||||||
|
python_is(Obj, O).
|
||||||
|
|
||||||
|
|
||||||
python_check_args(FRef, Exp, NExp) :-
|
python_check_args(FRef, Exp, NExp) :-
|
||||||
@ -136,26 +138,7 @@ match_args([A|LArgs], Dict, [A|NLArgs], not_ok) :-
|
|||||||
match_args(LArgs, Dict, NLArgs, _).
|
match_args(LArgs, Dict, NLArgs, _).
|
||||||
|
|
||||||
python(Obj, Out) :-
|
python(Obj, Out) :-
|
||||||
python_eval_term(Obj, Out), !.
|
python_eval_term(Obj, Out).
|
||||||
python(Obj, OArg) :-
|
|
||||||
python_do_is(Obj, Obj1),
|
|
||||||
python_is(Obj1, OArg).
|
|
||||||
|
|
||||||
python_do_is(A+B, NA+NB) :- !,
|
|
||||||
python_do_is(A, NA),
|
|
||||||
python_do_is(B, NB).
|
|
||||||
python_do_is(A-B, NA-NB) :- !,
|
|
||||||
python_do_is(A, NA),
|
|
||||||
python_do_is(B, NB).
|
|
||||||
python_do_is(A*B, NA*NB) :- !,
|
|
||||||
python_do_is(A, NA),
|
|
||||||
python_do_is(B, NB).
|
|
||||||
python_do_is(A/B, NA/NB) :- !,
|
|
||||||
python_do_is(A, NA),
|
|
||||||
python_do_is(B, NB).
|
|
||||||
python_do_is(A, NA) :-
|
|
||||||
python_eval_term(A, NA), !.
|
|
||||||
python_do_is(A, A).
|
|
||||||
|
|
||||||
python_command(Cmd) :-
|
python_command(Cmd) :-
|
||||||
python_run_command(Cmd).
|
python_run_command(Cmd).
|
||||||
|
Reference in New Issue
Block a user