inprove python interface.
This commit is contained in:
		
							
								
								
									
										131
									
								
								packages/python/examples/tut.pl
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										131
									
								
								packages/python/examples/tut.pl
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,131 @@
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					:- use_module(library(python)).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					:- initialization(main).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					main :- 
 | 
				
			||||||
 | 
						ex(X),
 | 
				
			||||||
 | 
						flush_output,
 | 
				
			||||||
 | 
						fail.
 | 
				
			||||||
 | 
					main.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					%
 | 
				
			||||||
 | 
					% strings are atoms in the interface
 | 
				
			||||||
 | 
					% with usual properties
 | 
				
			||||||
 | 
					%
 | 
				
			||||||
 | 
					% variables must be used with $
 | 
				
			||||||
 | 
					%
 | 
				
			||||||
 | 
					% UNICODE is supposed to work (does in Linux).
 | 
				
			||||||
 | 
					%
 | 
				
			||||||
 | 
					ex(currency) :-
 | 
				
			||||||
 | 
						(
 | 
				
			||||||
 | 
						    currency := '€',
 | 
				
			||||||
 | 
						    O := ord($currency),
 | 
				
			||||||
 | 
						    X := $currency,
 | 
				
			||||||
 | 
						    L := len($currency),
 | 
				
			||||||
 | 
						    format('currency=~a ~d/~d~n',[X, O, L])
 | 
				
			||||||
 | 
						->
 | 
				
			||||||
 | 
						    true
 | 
				
			||||||
 | 
						;
 | 
				
			||||||
 | 
						    failed(currency)
 | 
				
			||||||
 | 
						).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(home) :-
 | 
				
			||||||
 | 
						(
 | 
				
			||||||
 | 
						    filename := os:environ:get('HOME')
 | 
				
			||||||
 | 
						->
 | 
				
			||||||
 | 
						    X := $filename,
 | 
				
			||||||
 | 
						    format('HOME=~a~n',[X])
 | 
				
			||||||
 | 
						;
 | 
				
			||||||
 | 
						    true
 | 
				
			||||||
 | 
						).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(site) :-
 | 
				
			||||||
 | 
						X := site:getusersitepackages,
 | 
				
			||||||
 | 
						format('site packages=~a~n',[X]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(arith) :-
 | 
				
			||||||
 | 
						A := 2+2,
 | 
				
			||||||
 | 
						B := (50-5*6)/4,
 | 
				
			||||||
 | 
						C := 7/3,
 | 
				
			||||||
 | 
						width := 20,
 | 
				
			||||||
 | 
						height := 5*9,
 | 
				
			||||||
 | 
						D := $width* $height,
 | 
				
			||||||
 | 
						format('arith=~d ~d ~d ~d~n',[A,B,C,D]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(undefined) :-
 | 
				
			||||||
 | 
						format('undefined variable~n', []),
 | 
				
			||||||
 | 
						X := $n,
 | 
				
			||||||
 | 
						format('undefined=~d',[X]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(fp) :-
 | 
				
			||||||
 | 
						X := 3 * 3.75 / 1.5,
 | 
				
			||||||
 | 
						Y := 7.0 / 2,
 | 
				
			||||||
 | 
						format('fp=~f ~f~n',[X,Y]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(complex) :-
 | 
				
			||||||
 | 
						A := complex(0,1) * complex(0,1),
 | 
				
			||||||
 | 
						B := complex(3,1)*3,
 | 
				
			||||||
 | 
						a := complex(1.5,0.5),
 | 
				
			||||||
 | 
						R := $a:real,
 | 
				
			||||||
 | 
						I := $a:imag,
 | 
				
			||||||
 | 
						format('complex=~w ~w ~w+~wj~n',[A,B,R,I]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(floatint) :-
 | 
				
			||||||
 | 
						A := float(22000),
 | 
				
			||||||
 | 
						B := int(3.1),
 | 
				
			||||||
 | 
						C := long(15000000.5),
 | 
				
			||||||
 | 
						format('cast=~w ~w ~w~n',[A,B,C]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(strings) :-
 | 
				
			||||||
 | 
						S1 := 'spam eggs',
 | 
				
			||||||
 | 
						S2 := 'doesn\'t',
 | 
				
			||||||
 | 
						S3 := '"Yes," he said.',
 | 
				
			||||||
 | 
						S4 := '"Isn\'t," she said.',
 | 
				
			||||||
 | 
						format('s=~a ~a ~a ~a~n',[S1,S2,S3,S4]),
 | 
				
			||||||
 | 
						hello := 'This is a rather long string containing\n\
 | 
				
			||||||
 | 
					several lines of text just as you would do in C.\n\
 | 
				
			||||||
 | 
					    Note that whitespace at the beginning of the line is\
 | 
				
			||||||
 | 
					 significant.',
 | 
				
			||||||
 | 
						python_command('print hello'),
 | 
				
			||||||
 | 
						X := $hello,
 | 
				
			||||||
 | 
						format('s=~a~n',[X]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(strings2) :-
 | 
				
			||||||
 | 
						word := 'Help' + 'A',
 | 
				
			||||||
 | 
						X := '<' + $word*5 + '>',
 | 
				
			||||||
 | 
						Y := (str:strip) + ing,
 | 
				
			||||||
 | 
						A1 := $word^[4],
 | 
				
			||||||
 | 
						A2 := $word^[0:2],
 | 
				
			||||||
 | 
						A3 := $word^[2:4],
 | 
				
			||||||
 | 
						format('concat=~a ~a ~a ~a ~a~n',[X,Y,A1,A2,A3]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(slices) :-
 | 
				
			||||||
 | 
						s := 'supercalifragilisticexpialidocious',
 | 
				
			||||||
 | 
						L := len($s),
 | 
				
			||||||
 | 
						S1 := $s^[1:6],
 | 
				
			||||||
 | 
						S2 := $s^[-6: -1],
 | 
				
			||||||
 | 
						S3 := $s^[_:6],
 | 
				
			||||||
 | 
						S4 := $s^[-6:_],
 | 
				
			||||||
 | 
						format('slices=~d ~a ~a ~a ~a~n',[L,S1,S2,S3,S4]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ex(lists) :-
 | 
				
			||||||
 | 
						a := [66.25, 333, 333, 1, 1234.5],
 | 
				
			||||||
 | 
					        A1 := $a:count(333), A2 := $a:count(66.25), A3 := $a:count('x'),
 | 
				
			||||||
 | 
						format('counts=~d ~d ~d~n',[A1,A2,A3]),
 | 
				
			||||||
 | 
						:= $a:insert(2, -1),
 | 
				
			||||||
 | 
						:= $a:append(333),
 | 
				
			||||||
 | 
						A := $a,
 | 
				
			||||||
 | 
						format('a=~w~n', [A]),
 | 
				
			||||||
 | 
						I := $a:index(333),
 | 
				
			||||||
 | 
						:= $a:remove(333),
 | 
				
			||||||
 | 
						B := $a,
 | 
				
			||||||
 | 
						format('a=~w~n', [B]),
 | 
				
			||||||
 | 
						:= $a:reverse,
 | 
				
			||||||
 | 
						C := $a,
 | 
				
			||||||
 | 
						format('a=~w~n', [C]),
 | 
				
			||||||
 | 
						:= $a:sort,
 | 
				
			||||||
 | 
						D := $a,
 | 
				
			||||||
 | 
						format('a=~w~n', [D]).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@@ -7,6 +7,7 @@
 | 
				
			|||||||
#include <assert.h>
 | 
					#include <assert.h>
 | 
				
			||||||
 | 
					
 | 
				
			||||||
static atom_t ATOM_true,
 | 
					static atom_t ATOM_true,
 | 
				
			||||||
 | 
					  ATOM_colon,
 | 
				
			||||||
  ATOM_false,
 | 
					  ATOM_false,
 | 
				
			||||||
  ATOM_t;
 | 
					  ATOM_t;
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@@ -16,6 +17,9 @@ static functor_t FUNCTOR_dollar1,
 | 
				
			|||||||
  FUNCTOR_any1, 
 | 
					  FUNCTOR_any1, 
 | 
				
			||||||
  FUNCTOR_bin1, 
 | 
					  FUNCTOR_bin1, 
 | 
				
			||||||
  FUNCTOR_dir1, 
 | 
					  FUNCTOR_dir1, 
 | 
				
			||||||
 | 
					  FUNCTOR_float1, 
 | 
				
			||||||
 | 
					  FUNCTOR_int1, 
 | 
				
			||||||
 | 
					  FUNCTOR_long1, 
 | 
				
			||||||
  FUNCTOR_iter1, 
 | 
					  FUNCTOR_iter1, 
 | 
				
			||||||
  FUNCTOR_len1, 
 | 
					  FUNCTOR_len1, 
 | 
				
			||||||
  FUNCTOR_curly1,
 | 
					  FUNCTOR_curly1,
 | 
				
			||||||
@@ -185,6 +189,66 @@ bip_bin(term_t t)
 | 
				
			|||||||
}
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					static PyObject *
 | 
				
			||||||
 | 
					bip_float(term_t t)
 | 
				
			||||||
 | 
					{
 | 
				
			||||||
 | 
					  PyObject *pVal, *o;
 | 
				
			||||||
 | 
						
 | 
				
			||||||
 | 
					  if (! PL_get_arg(1, t, t) )
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  pVal = term_to_python(t);
 | 
				
			||||||
 | 
					  if (PyLong_Check(pVal)) {
 | 
				
			||||||
 | 
					    o = PyFloat_FromDouble( PyLong_AsLong(pVal) );
 | 
				
			||||||
 | 
					  } else if (PyInt_Check(pVal)) {
 | 
				
			||||||
 | 
					    o =  PyFloat_FromDouble( PyInt_AsLong(pVal) );
 | 
				
			||||||
 | 
					  } else if (PyFloat_Check(pVal)) {
 | 
				
			||||||
 | 
					    return pVal;
 | 
				
			||||||
 | 
					  } else
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  Py_DECREF(pVal);
 | 
				
			||||||
 | 
					  return o;
 | 
				
			||||||
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					static PyObject *
 | 
				
			||||||
 | 
					bip_int(term_t t)
 | 
				
			||||||
 | 
					{
 | 
				
			||||||
 | 
					  PyObject *pVal, *o;
 | 
				
			||||||
 | 
						
 | 
				
			||||||
 | 
					  if (! PL_get_arg(1, t, t) )
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  pVal = term_to_python(t);
 | 
				
			||||||
 | 
					  if (PyLong_Check(pVal)) {
 | 
				
			||||||
 | 
					    o = PyInt_FromLong( PyLong_AsLong(pVal) );
 | 
				
			||||||
 | 
					  } else if (PyInt_Check(pVal)) {
 | 
				
			||||||
 | 
					    return pVal;
 | 
				
			||||||
 | 
					  } else if (PyFloat_Check(pVal)) {
 | 
				
			||||||
 | 
					    o = PyInt_FromLong( PyFloat_AsDouble(pVal) );
 | 
				
			||||||
 | 
					  } else
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  Py_DECREF(pVal);
 | 
				
			||||||
 | 
					  return o;
 | 
				
			||||||
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					static PyObject *
 | 
				
			||||||
 | 
					bip_long(term_t t)
 | 
				
			||||||
 | 
					{
 | 
				
			||||||
 | 
					  PyObject *pVal, *o;
 | 
				
			||||||
 | 
						
 | 
				
			||||||
 | 
					  if (! PL_get_arg(1, t, t) )
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  pVal = term_to_python(t);
 | 
				
			||||||
 | 
					  if (PyLong_Check(pVal)) {
 | 
				
			||||||
 | 
					    return pVal;
 | 
				
			||||||
 | 
					  } else if (PyLong_Check(pVal)) {
 | 
				
			||||||
 | 
					    o = PyLong_FromLong( PyInt_AsLong(pVal) );
 | 
				
			||||||
 | 
					  } else if (PyFloat_Check(pVal)) {
 | 
				
			||||||
 | 
					    o = PyLong_FromLong( PyFloat_AsDouble(pVal) );
 | 
				
			||||||
 | 
					  } else
 | 
				
			||||||
 | 
					    return NULL;
 | 
				
			||||||
 | 
					  Py_DECREF(pVal);
 | 
				
			||||||
 | 
					  return o;
 | 
				
			||||||
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
static PyObject *
 | 
					static PyObject *
 | 
				
			||||||
bip_ord(term_t t)
 | 
					bip_ord(term_t t)
 | 
				
			||||||
{
 | 
					{
 | 
				
			||||||
@@ -330,6 +394,12 @@ term_to_python(term_t t)
 | 
				
			|||||||
	return bip_bin(t);
 | 
						return bip_bin(t);
 | 
				
			||||||
      } else if (fun == FUNCTOR_ord1) {
 | 
					      } else if (fun == FUNCTOR_ord1) {
 | 
				
			||||||
	return bip_ord(t);
 | 
						return bip_ord(t);
 | 
				
			||||||
 | 
					      } else if (fun == FUNCTOR_int1) {
 | 
				
			||||||
 | 
						return bip_int(t);
 | 
				
			||||||
 | 
					      } else if (fun == FUNCTOR_long1) {
 | 
				
			||||||
 | 
						return bip_long(t);
 | 
				
			||||||
 | 
					      } else if (fun == FUNCTOR_float1) {
 | 
				
			||||||
 | 
						return bip_float(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;
 | 
				
			||||||
@@ -755,9 +825,9 @@ python_import(term_t mname, term_t mod)
 | 
				
			|||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
  pModule = PyImport_Import(pName);
 | 
					  pModule = PyImport_Import(pName);
 | 
				
			||||||
  // PyErr_Print();
 | 
					 | 
				
			||||||
  Py_DECREF(pName);
 | 
					  Py_DECREF(pName);
 | 
				
			||||||
  if (pModule == NULL) {
 | 
					  if (pModule == NULL) {
 | 
				
			||||||
 | 
					    PyErr_Clear();
 | 
				
			||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
  return python_to_term(pModule, mod);
 | 
					  return python_to_term(pModule, mod);
 | 
				
			||||||
@@ -788,6 +858,7 @@ python_f(term_t tmod, term_t fname, term_t tf)
 | 
				
			|||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
  pF = PyObject_GetAttrString(pModule, s);
 | 
					  pF = PyObject_GetAttrString(pModule, s);
 | 
				
			||||||
 | 
					  PyErr_Print();
 | 
				
			||||||
  Py_DECREF(pModule);
 | 
					  Py_DECREF(pModule);
 | 
				
			||||||
  if (pF == NULL || ! PyCallable_Check(pF)) {
 | 
					  if (pF == NULL || ! PyCallable_Check(pF)) {
 | 
				
			||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
@@ -867,6 +938,24 @@ python_apply(term_t tin, term_t targs, term_t tf)
 | 
				
			|||||||
  if (! PL_get_name_arity( targs, &aname, &arity) ) {
 | 
					  if (! PL_get_name_arity( targs, &aname, &arity) ) {
 | 
				
			||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					  /* follow chains of the form a.b.c.d.e() */
 | 
				
			||||||
 | 
					  while (aname == ATOM_colon && arity == 2) {
 | 
				
			||||||
 | 
					    term_t tleft = PL_new_term_ref();
 | 
				
			||||||
 | 
					    PyObject *lhs;
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					    if (! PL_get_arg(1, targs, tleft) )
 | 
				
			||||||
 | 
					      return FALSE;
 | 
				
			||||||
 | 
					    lhs = term_to_python(tleft);
 | 
				
			||||||
 | 
					    if ((pF = PyObject_GetAttr(pF, lhs)) == NULL) {
 | 
				
			||||||
 | 
					      PyErr_Print();
 | 
				
			||||||
 | 
					      return FALSE;
 | 
				
			||||||
 | 
					    }
 | 
				
			||||||
 | 
					    if (! PL_get_arg(2, targs, targs) )
 | 
				
			||||||
 | 
					      return FALSE;    
 | 
				
			||||||
 | 
					    if (! PL_get_name_arity( targs, &aname, &arity) ) {
 | 
				
			||||||
 | 
					      return FALSE;
 | 
				
			||||||
 | 
					    }    
 | 
				
			||||||
 | 
					  }
 | 
				
			||||||
  if (PyFunction_Check(pF)) {
 | 
					  if (PyFunction_Check(pF)) {
 | 
				
			||||||
    int tuple_inited = FALSE;
 | 
					    int tuple_inited = FALSE;
 | 
				
			||||||
    PyObject *pOpt = NULL;
 | 
					    PyObject *pOpt = NULL;
 | 
				
			||||||
@@ -916,14 +1005,16 @@ python_apply(term_t tin, term_t targs, term_t tf)
 | 
				
			|||||||
  }
 | 
					  }
 | 
				
			||||||
  if (PyCallable_Check(pF)) {
 | 
					  if (PyCallable_Check(pF)) {
 | 
				
			||||||
    pValue = PyObject_CallObject(pF, pArgs);      
 | 
					    pValue = PyObject_CallObject(pF, pArgs);      
 | 
				
			||||||
 | 
					    PyErr_Print();
 | 
				
			||||||
  } else {
 | 
					  } else {
 | 
				
			||||||
 | 
					    PyErr_Print();
 | 
				
			||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
  PyErr_Print();
 | 
					  PyErr_Print();
 | 
				
			||||||
  Py_DECREF(pArgs);
 | 
					  Py_DECREF(pArgs);
 | 
				
			||||||
 | 
					  Py_DECREF(pF);
 | 
				
			||||||
  if (pValue == NULL)
 | 
					  if (pValue == NULL)
 | 
				
			||||||
      return FALSE;
 | 
					      return FALSE;
 | 
				
			||||||
  out = 0;
 | 
					 | 
				
			||||||
  out =  python_to_term(pValue, tf);
 | 
					  out =  python_to_term(pValue, tf);
 | 
				
			||||||
  Py_DECREF(pValue);
 | 
					  Py_DECREF(pValue);
 | 
				
			||||||
  return out;
 | 
					  return out;
 | 
				
			||||||
@@ -953,8 +1044,10 @@ python_access(term_t obj, term_t f, term_t out)
 | 
				
			|||||||
  if ( PL_is_atom(f) ) {
 | 
					  if ( PL_is_atom(f) ) {
 | 
				
			||||||
    if (!PL_get_atom_chars(f, &s))
 | 
					    if (!PL_get_atom_chars(f, &s))
 | 
				
			||||||
      return FALSE;
 | 
					      return FALSE;
 | 
				
			||||||
    if ((pValue = PyObject_GetAttrString(o, s)) == NULL)
 | 
					    if ((pValue = PyObject_GetAttrString(o, s)) == NULL) {
 | 
				
			||||||
 | 
					      PyErr_Print();
 | 
				
			||||||
      return FALSE;  
 | 
					      return FALSE;  
 | 
				
			||||||
 | 
					    }
 | 
				
			||||||
    if ( PyCallable_Check(pValue) )
 | 
					    if ( PyCallable_Check(pValue) )
 | 
				
			||||||
      pValue = PyObject_CallObject(pValue, NULL);
 | 
					      pValue = PyObject_CallObject(pValue, NULL);
 | 
				
			||||||
    PyErr_Print();
 | 
					    PyErr_Print();
 | 
				
			||||||
@@ -963,6 +1056,24 @@ python_access(term_t obj, term_t f, term_t out)
 | 
				
			|||||||
  if (! PL_get_name_arity( f, &name, &arity) ) {
 | 
					  if (! PL_get_name_arity( f, &name, &arity) ) {
 | 
				
			||||||
    return FALSE;
 | 
					    return FALSE;
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					  /* follow chains of the form a.b.c.d.e() */
 | 
				
			||||||
 | 
					  while (name == ATOM_colon && arity == 2) {
 | 
				
			||||||
 | 
					    term_t tleft = PL_new_term_ref();
 | 
				
			||||||
 | 
					    PyObject *lhs;
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					    if (! PL_get_arg(1, f, tleft) )
 | 
				
			||||||
 | 
					      return FALSE;
 | 
				
			||||||
 | 
					    lhs = term_to_python(tleft);
 | 
				
			||||||
 | 
					    if ((o = PyObject_GetAttr(o, lhs)) == NULL) {
 | 
				
			||||||
 | 
					      PyErr_Print();
 | 
				
			||||||
 | 
					      return FALSE;        
 | 
				
			||||||
 | 
					    }
 | 
				
			||||||
 | 
					    if (! PL_get_arg(2, f, f) )
 | 
				
			||||||
 | 
					      return FALSE;    
 | 
				
			||||||
 | 
					    if (! PL_get_name_arity( f, &name, &arity) ) {
 | 
				
			||||||
 | 
					      return FALSE;
 | 
				
			||||||
 | 
					    }    
 | 
				
			||||||
 | 
					  }
 | 
				
			||||||
  s = PL_atom_chars(name);
 | 
					  s = PL_atom_chars(name);
 | 
				
			||||||
  if ((pF = PyObject_GetAttrString(o, s)) == NULL) {
 | 
					  if ((pF = PyObject_GetAttrString(o, s)) == NULL) {
 | 
				
			||||||
    PyErr_Print();
 | 
					    PyErr_Print();
 | 
				
			||||||
@@ -1028,6 +1139,7 @@ install_python(void)
 | 
				
			|||||||
{ // FUNCTOR_dot2 = PL_new_functor(PL_new_atom("."), 2);
 | 
					{ // FUNCTOR_dot2 = PL_new_functor(PL_new_atom("."), 2);
 | 
				
			||||||
  // FUNCTOR_equal2 = PL_new_functor(PL_new_atom("="), 2);
 | 
					  // FUNCTOR_equal2 = PL_new_functor(PL_new_atom("="), 2);
 | 
				
			||||||
  // FUNCTOR_boolop1 = PL_new_functor(PL_new_atom("@"), 1);
 | 
					  // FUNCTOR_boolop1 = PL_new_functor(PL_new_atom("@"), 1);
 | 
				
			||||||
 | 
					  ATOM_colon = PL_new_atom(":");
 | 
				
			||||||
  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");
 | 
					  ATOM_t = PL_new_atom("t");
 | 
				
			||||||
@@ -1036,6 +1148,9 @@ install_python(void)
 | 
				
			|||||||
  FUNCTOR_any1 = PL_new_functor(PL_new_atom("any"), 1);
 | 
					  FUNCTOR_any1 = PL_new_functor(PL_new_atom("any"), 1);
 | 
				
			||||||
  FUNCTOR_bin1 = PL_new_functor(PL_new_atom("bin"), 1);
 | 
					  FUNCTOR_bin1 = PL_new_functor(PL_new_atom("bin"), 1);
 | 
				
			||||||
  FUNCTOR_ord1 = PL_new_functor(PL_new_atom("ord"), 1);
 | 
					  FUNCTOR_ord1 = PL_new_functor(PL_new_atom("ord"), 1);
 | 
				
			||||||
 | 
					  FUNCTOR_int1 = PL_new_functor(PL_new_atom("int"), 1);
 | 
				
			||||||
 | 
					  FUNCTOR_long1 = PL_new_functor(PL_new_atom("long"), 1);
 | 
				
			||||||
 | 
					  FUNCTOR_float1 = PL_new_functor(PL_new_atom("float"), 1);
 | 
				
			||||||
  FUNCTOR_curly1 = PL_new_functor(PL_new_atom("{}"), 1);
 | 
					  FUNCTOR_curly1 = PL_new_functor(PL_new_atom("{}"), 1);
 | 
				
			||||||
  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);
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -98,6 +98,10 @@ python_eval_term(Expression, O) :-
 | 
				
			|||||||
	    atom(Exp)
 | 
						    atom(Exp)
 | 
				
			||||||
        ->
 | 
					        ->
 | 
				
			||||||
	    python_access(MRef, Exp, O)
 | 
						    python_access(MRef, Exp, O)
 | 
				
			||||||
 | 
						;
 | 
				
			||||||
 | 
						    Exp = Obj:Method
 | 
				
			||||||
 | 
					        ->
 | 
				
			||||||
 | 
						    python_access(MRef, Exp, O)
 | 
				
			||||||
	;
 | 
						;
 | 
				
			||||||
	    functor(Exp, F, _),
 | 
						    functor(Exp, F, _),
 | 
				
			||||||
	    python_f(MRef, F, FRef),
 | 
						    python_f(MRef, F, FRef),
 | 
				
			||||||
@@ -115,12 +119,12 @@ python_check_args(FRef, Exp, NExp) :-
 | 
				
			|||||||
	Exp =.. [F|LArgs],
 | 
						Exp =.. [F|LArgs],
 | 
				
			||||||
	match_args(LArgs, Dict, NLArgs, _),
 | 
						match_args(LArgs, Dict, NLArgs, _),
 | 
				
			||||||
	NExp =.. [F|NLArgs].
 | 
						NExp =.. [F|NLArgs].
 | 
				
			||||||
python_check_args(FRef, Exp, NExp).
 | 
					python_check_args(FRef, Exp, Exp).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
fetch_args(FRef, Args) :-
 | 
					fetch_args(FRef, Args) :-
 | 
				
			||||||
	python_import('inspect', M),
 | 
						python_import('inspect', M),
 | 
				
			||||||
	python_f(M, getargspec, F),
 | 
						python_f(M, getargspec, F),
 | 
				
			||||||
	python_apply(F, getargspec(FRef), ExtraArgs),
 | 
						python_apply(F, getargspec(FRef), Args),
 | 
				
			||||||
	ExtraArgs=t(Args, _, _, _).
 | 
						ExtraArgs=t(Args, _, _, _).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 
 | 
				
			|||||||
		Reference in New Issue
	
	Block a user