more support.
This commit is contained in:
parent
ea3f2f13e9
commit
f33fe61ada
35
packages/pyswip/pl2py_examples/nltk.pl
Normal file
35
packages/pyswip/pl2py_examples/nltk.pl
Normal file
@ -0,0 +1,35 @@
|
|||||||
|
:- use_module(library(python)).
|
||||||
|
:- use_module(library(maplist)).
|
||||||
|
|
||||||
|
main :-
|
||||||
|
main(Sentence, Tokens, Tagged),
|
||||||
|
writeln(Sentence),
|
||||||
|
writeln(tokens=Tokens),
|
||||||
|
writeln(tagged=Tagged),
|
||||||
|
fail.
|
||||||
|
main :-
|
||||||
|
Sentence = 'Debutta a New York il nuovo sistema operativo (cronaca in diretta). E c\'è il tablet Surface. Svolta radicale che strizza l\'occhio al mondo touch per l\'azienda che controlla il 92% dei pc dal nostro inviato M. Serafini',
|
||||||
|
% c = nltk.stem.snowball.ItalianStemmer("italian')
|
||||||
|
$c := nltk:stem:snowball:'ItalianStemmer'(italian),
|
||||||
|
Tokens := nltk:word_tokenize(Sentence),
|
||||||
|
writeln(tokens=Tokens),
|
||||||
|
% o = c.stem('voglio')
|
||||||
|
maplist(process, Tokens, Stems),
|
||||||
|
writeln(stems=Stems).
|
||||||
|
|
||||||
|
process(In, Out) :-
|
||||||
|
Out := $c:stem(In),
|
||||||
|
writeln(In:=Out).
|
||||||
|
process(In, In).
|
||||||
|
|
||||||
|
main(Sentence, Tokens, Tagged) :-
|
||||||
|
Sentence = '\"At eight o\'clock on Thursday morning\
|
||||||
|
... Arthur didn\'t feel very good.\"',
|
||||||
|
Tokens := nltk:word_tokenize(Sentence),
|
||||||
|
%['At', 'eight', "o'clock", 'on', 'Thursday', 'morning',
|
||||||
|
% 'Arthur', 'did', "n't", 'feel', 'very', 'good', '.']
|
||||||
|
Tagged := nltk:pos_tag(Tokens).
|
||||||
|
%>>> tagged[0:6]
|
||||||
|
%[('At', 'IN'), ('eight', 'CD'), ("o'clock", 'JJ'), ('on', 'IN'),
|
||||||
|
%('Thursday', 'NNP'), ('morning', 'NN')]
|
||||||
|
|
@ -6,7 +6,9 @@
|
|||||||
#include <Python.h>
|
#include <Python.h>
|
||||||
#include <assert.h>
|
#include <assert.h>
|
||||||
|
|
||||||
static atom_t ATOM_true, ATOM_false;
|
static atom_t ATOM_true,
|
||||||
|
ATOM_false,
|
||||||
|
ATOM_t;
|
||||||
|
|
||||||
static functor_t FUNCTOR_dollar1,
|
static functor_t FUNCTOR_dollar1,
|
||||||
FUNCTOR_pointer1,
|
FUNCTOR_pointer1,
|
||||||
@ -31,7 +33,7 @@ term_to_python(term_t t)
|
|||||||
|
|
||||||
if (!PL_get_atom_chars(t, &s))
|
if (!PL_get_atom_chars(t, &s))
|
||||||
return NULL;
|
return NULL;
|
||||||
return PyByteArray_FromStringAndSize(s, strlen(s) );
|
return PyString_FromStringAndSize(s, strlen(s) );
|
||||||
}
|
}
|
||||||
case PL_INTEGER:
|
case PL_INTEGER:
|
||||||
{
|
{
|
||||||
@ -195,12 +197,33 @@ python_to_term(PyObject *pVal, term_t t)
|
|||||||
}
|
}
|
||||||
} else if (PyFloat_Check(pVal)) {
|
} else if (PyFloat_Check(pVal)) {
|
||||||
return PL_unify_float(t, PyFloat_AsDouble(pVal));
|
return PL_unify_float(t, PyFloat_AsDouble(pVal));
|
||||||
|
} else if (PyUnicode_Check(pVal)) {
|
||||||
|
Py_ssize_t sz = PyUnicode_GetSize(pVal)+1;
|
||||||
|
wchar_t *ptr;
|
||||||
|
ptr = malloc(sizeof(wchar_t)*sz);
|
||||||
|
sz = PyUnicode_AsWideChar((struct PyUnicodeObject *)pVal, ptr, sz-1);
|
||||||
|
atom_t tmp_atom = PL_new_atom_wchars(sz,ptr);
|
||||||
|
free(ptr);
|
||||||
|
return PL_unify_atom(t, tmp_atom);
|
||||||
} else if (PyByteArray_Check(pVal)) {
|
} else if (PyByteArray_Check(pVal)) {
|
||||||
atom_t tmp_atom = PL_new_atom(PyByteArray_AsString(pVal));
|
atom_t tmp_atom = PL_new_atom(PyByteArray_AsString(pVal));
|
||||||
return PL_unify_atom(t, tmp_atom);
|
return PL_unify_atom(t, tmp_atom);
|
||||||
} else if (PyString_Check(pVal)) {
|
} else if (PyString_Check(pVal)) {
|
||||||
atom_t tmp_atom = PL_new_atom(PyString_AsString(pVal));
|
atom_t tmp_atom = PL_new_atom(PyString_AsString(pVal));
|
||||||
return PL_unify_atom(t, tmp_atom);
|
return PL_unify_atom(t, tmp_atom);
|
||||||
|
} else if (PyTuple_Check(pVal)) {
|
||||||
|
Py_ssize_t i, sz = PyTuple_GET_SIZE(pVal);
|
||||||
|
functor_t f = PL_new_functor(ATOM_t, 2);
|
||||||
|
if (!PL_unify_functor(t, f))
|
||||||
|
return FALSE;
|
||||||
|
for (i = 0; i < sz; i++) {
|
||||||
|
term_t to = PL_new_term_ref();
|
||||||
|
if (!PL_unify_arg(i+1, t, to))
|
||||||
|
return FALSE;
|
||||||
|
if ( !python_to_term(PyTuple_GetItem(pVal, i), to) )
|
||||||
|
return FALSE;
|
||||||
|
}
|
||||||
|
return TRUE;
|
||||||
} else if (PyList_Check(pVal)) {
|
} else if (PyList_Check(pVal)) {
|
||||||
term_t to = PL_new_term_ref();
|
term_t to = PL_new_term_ref();
|
||||||
Py_ssize_t i, sz = PyList_GET_SIZE(pVal);
|
Py_ssize_t i, sz = PyList_GET_SIZE(pVal);
|
||||||
@ -215,6 +238,7 @@ python_to_term(PyObject *pVal, term_t t)
|
|||||||
term_t to = PL_new_term_ref(), t1 = PL_new_term_ref();
|
term_t to = PL_new_term_ref(), t1 = PL_new_term_ref();
|
||||||
PL_put_pointer(t1, (void *)pVal);
|
PL_put_pointer(t1, (void *)pVal);
|
||||||
PL_cons_functor(to, FUNCTOR_pointer1, t1);
|
PL_cons_functor(to, FUNCTOR_pointer1, t1);
|
||||||
|
Py_INCREF(pVal);
|
||||||
return PL_unify(t, to);
|
return PL_unify(t, to);
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
@ -350,7 +374,8 @@ python_is(term_t tobj, term_t tf)
|
|||||||
static foreign_t
|
static foreign_t
|
||||||
python_apply(term_t tin, term_t targs, term_t tf)
|
python_apply(term_t tin, term_t targs, term_t tf)
|
||||||
{
|
{
|
||||||
PyObject *pF, *pArgs, *pValue;
|
PyObject *pF, *pValue;
|
||||||
|
PyObject *pArgs;
|
||||||
int i, arity;
|
int i, arity;
|
||||||
atom_t aname;
|
atom_t aname;
|
||||||
foreign_t out;
|
foreign_t out;
|
||||||
@ -374,10 +399,15 @@ python_apply(term_t tin, term_t targs, term_t tf)
|
|||||||
/* pArg reference stolen here: */
|
/* pArg reference stolen here: */
|
||||||
PyTuple_SetItem(pArgs, i, pArg);
|
PyTuple_SetItem(pArgs, i, pArg);
|
||||||
}
|
}
|
||||||
pValue = PyObject_CallObject(pF, pArgs);
|
if (PyCallable_Check(pF)) {
|
||||||
|
pValue = PyObject_CallObject(pF, pArgs);
|
||||||
|
} else {
|
||||||
|
return FALSE;
|
||||||
|
}
|
||||||
|
PyErr_Print();
|
||||||
Py_DECREF(pArgs);
|
Py_DECREF(pArgs);
|
||||||
if (pValue == NULL)
|
if (pValue == NULL)
|
||||||
return FALSE;
|
return FALSE;
|
||||||
out = python_to_term(pValue, tf);
|
out = python_to_term(pValue, tf);
|
||||||
Py_DECREF(pValue);
|
Py_DECREF(pValue);
|
||||||
return out;
|
return out;
|
||||||
@ -412,14 +442,19 @@ python_access(term_t obj, term_t f, term_t out)
|
|||||||
return FALSE;
|
return FALSE;
|
||||||
if ((pValue = PyObject_GetAttrString(o, s)) == NULL)
|
if ((pValue = PyObject_GetAttrString(o, s)) == NULL)
|
||||||
return FALSE;
|
return FALSE;
|
||||||
|
if ( PyCallable_Check(pValue) )
|
||||||
|
pValue = PyObject_CallObject(pValue, NULL);
|
||||||
|
PyErr_Print();
|
||||||
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) ) {
|
||||||
return FALSE;
|
return FALSE;
|
||||||
}
|
}
|
||||||
s = PL_atom_chars(name);
|
s = PL_atom_chars(name);
|
||||||
if ((pF = PyObject_GetAttrString(o, s)) < 0)
|
if ((pF = PyObject_GetAttrString(o, s)) == NULL) {
|
||||||
|
PyErr_Print();
|
||||||
return FALSE;
|
return FALSE;
|
||||||
|
}
|
||||||
pArgs = PyTuple_New(arity);
|
pArgs = PyTuple_New(arity);
|
||||||
for (i = 0 ; i < arity; i++) {
|
for (i = 0 ; i < arity; i++) {
|
||||||
PyObject *pArg;
|
PyObject *pArg;
|
||||||
@ -439,7 +474,7 @@ python_access(term_t obj, term_t f, term_t out)
|
|||||||
}
|
}
|
||||||
Py_DECREF(pArgs);
|
Py_DECREF(pArgs);
|
||||||
Py_DECREF(pF);
|
Py_DECREF(pF);
|
||||||
return python_to_term(o, out);
|
return python_to_term(pValue, out);
|
||||||
}
|
}
|
||||||
|
|
||||||
static foreign_t
|
static foreign_t
|
||||||
@ -482,6 +517,7 @@ install_python(void)
|
|||||||
// FUNCTOR_boolop1 = PL_new_functor(PL_new_atom("@"), 1);
|
// FUNCTOR_boolop1 = PL_new_functor(PL_new_atom("@"), 1);
|
||||||
ATOM_true = PL_new_atom("true");
|
ATOM_true = PL_new_atom("true");
|
||||||
ATOM_false = PL_new_atom("false");
|
ATOM_false = PL_new_atom("false");
|
||||||
|
ATOM_t = PL_new_atom("t");
|
||||||
FUNCTOR_dollar1 = PL_new_functor(PL_new_atom("$"), 1);
|
FUNCTOR_dollar1 = PL_new_functor(PL_new_atom("$"), 1);
|
||||||
FUNCTOR_pointer1 = PL_new_functor(PL_new_atom("__obj__"), 1);
|
FUNCTOR_pointer1 = PL_new_functor(PL_new_atom("__obj__"), 1);
|
||||||
FUNCTOR_add2 = PL_new_functor(PL_new_atom("+"), 2);
|
FUNCTOR_add2 = PL_new_functor(PL_new_atom("+"), 2);
|
||||||
|
@ -28,6 +28,7 @@ A C-based Prolog interface to python.
|
|||||||
end_python/0,
|
end_python/0,
|
||||||
python_command/1,
|
python_command/1,
|
||||||
python_assign/3,
|
python_assign/3,
|
||||||
|
python_import/1,
|
||||||
python/2,
|
python/2,
|
||||||
op(100,fy,$),
|
op(100,fy,$),
|
||||||
op(950,fy,:=),
|
op(950,fy,:=),
|
||||||
@ -47,9 +48,10 @@ Data types are
|
|||||||
string atoms
|
string atoms
|
||||||
numbers numbers
|
numbers numbers
|
||||||
lists lists
|
lists lists
|
||||||
|
tuples t(...)
|
||||||
generic objs __pointer__(Address)
|
generic objs __pointer__(Address)
|
||||||
|
|
||||||
$(var) refers to the attribute __main__.var
|
$var refers to the attribute __main__.var
|
||||||
|
|
||||||
*************************************************************************************************************/
|
*************************************************************************************************************/
|
||||||
|
|
||||||
@ -66,38 +68,44 @@ V := F :- var(V), !, python(F,V).
|
|||||||
'$'(V) := F :- atom(V), !, python(F,F1), python_assign(V, F1).
|
'$'(V) := F :- atom(V), !, python(F,F1), python_assign(V, F1).
|
||||||
A^Key := F :- python(F,F1), python_set_item(A, Key, F1).
|
A^Key := F :- python(F,F1), python_set_item(A, Key, F1).
|
||||||
|
|
||||||
|
python_import(Module) :-
|
||||||
|
python_do_import(Module, _).
|
||||||
|
|
||||||
python_do_import(Module, MRef) :-
|
python_do_import(Module, MRef) :-
|
||||||
python_mref_cache(Module, MRef), !.
|
python_mref_cache(Module, MRef), !.
|
||||||
python_do_import(Module, MRef) :-
|
python_do_import(Module, MRef) :-
|
||||||
python_import(Module, MRef),
|
python_import(Module, MRef),
|
||||||
assert( python_mref_cache(Module, MRef) ).
|
assert( python_mref_cache(Module, MRef) ).
|
||||||
|
|
||||||
python_eval_term(Object:len, OArg) :- !,
|
fetch_module(M:E, M1, E1, MRef) :-
|
||||||
python_len(Object, OArg).
|
atom(M),
|
||||||
python_eval_term(Module:Object:len, OArg) :- !,
|
python_import(M, MRef0),
|
||||||
python_do_import(Module, MRef),
|
module_extend(M, E, M1, E1, MRef0, MRef).
|
||||||
python_o(MRef, Function, ORef),
|
|
||||||
python_len(ORef, OArg).
|
%
|
||||||
python_eval_term(Object:dir, OArg) :- !,
|
% extend the module as much as we can.
|
||||||
python_dir(Object, OArg).
|
%
|
||||||
python_eval_term(Module:Object:dir, OArg) :- !,
|
module_extend(M0, M:E, MF, EF, MRef0, MRef) :-
|
||||||
python_do_import(Module, MRef),
|
atom(M),
|
||||||
python_o(MRef, Function, ORef),
|
atom_concat([M0,'.',M], MM),
|
||||||
python_dir(ORef, OArg).
|
python_import(MM, MRef1), !,
|
||||||
python_eval_term(Module:Object:Field, OArg) :-
|
module_extend(MM, E, MF, EF, MRef1, MRef).
|
||||||
atom(Module),
|
module_extend(M, E, M, E, MRef, MRef).
|
||||||
atom(Object), !,
|
|
||||||
python_do_import(Module, MRef),
|
% given an object, detect its len method
|
||||||
python_o(MRef, Function, ORef),
|
python_eval_term(Expression, O) :-
|
||||||
python_access(ORef, Field, OArg).
|
fetch_module(Expression, Module, Exp, MRef), !,
|
||||||
python_eval_term(Module:Function, OArg) :-
|
(
|
||||||
atom(Module), !,
|
atom(Exp)
|
||||||
python_do_import(Module, MRef),
|
->
|
||||||
functor(Function, F, _),
|
python_access(MRef, Exp, O)
|
||||||
python_f(MRef, F, FRef),
|
;
|
||||||
python_apply(FRef, Function, OArg).
|
functor(Exp, F, _),
|
||||||
python_eval_term(Obj:Field, OArg) :-
|
python_f(MRef, F, FRef),
|
||||||
python_access(Obj, Field, OArg).
|
python_apply(FRef, Exp, O)
|
||||||
|
).
|
||||||
|
python_eval_term(Obj:Field, O) :-
|
||||||
|
python_access(Obj, Field, O).
|
||||||
|
|
||||||
python(Obj, Out) :-
|
python(Obj, Out) :-
|
||||||
python_eval_term(Obj, Out), !.
|
python_eval_term(Obj, Out), !.
|
||||||
|
Reference in New Issue
Block a user