% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(janus): Call Python from Prolog} \label{sec:janus} This library implements calling Python from Prolog. It is available directly from Prolog if the janus package is bundled, providing access to an \textit{embedded} Python instance. If SWI-Prolog is embedded into Python using the Python package \verb$janus-swi$, this library is provided either from Prolog or from the Python package. Normally, the Prolog user can simply start calling Python using \predref{py_call}{2} or friends. In special cases it may be needed to initialize Python with options using \predref{py_initialize}{3} and optionally the Python search path may be extended using \predref{py_add_lib_dir}{1}.\vspace{0.7cm} \begin{description} \predicate[det]{py_version}{0}{} Print version info on the embedded Python installation based on Python \verb$sys:version$. \predicate[det]{py_call}{1}{+Call} \nodescription \predicate[det]{py_call}{2}{+Call, -Return} \nodescription \predicate[det]{py_call}{3}{+Call, -Return, +Options} \arg{Call} Python and return the result of the called function. \arg{Call} has the shape `[Target][:Action]*`, where \arg{Target} is either a Python module name or a Python object reference. Each \arg{Action} is either an atom to get the denoted attribute from current \arg{Target} or it is a compound term where the first argument is the function or method name and the arguments provide the parameters to the Python function. On success, the returned Python object is translated to Prolog. \arg{Action} without a \arg{Target} denotes a buit-in function. Arguments to Python functions use the Python conventions. Both \textit{positional} and \textit{keyword} arguments are supported. Keyword arguments are written as \verb$Name = Value$ and must appear after the positional arguments. Below are some examples. \begin{code} % call a built-in ?- py_call(print("Hello World!\n")). true. % call a built-in (alternative) ?- py_call(builtins:print("Hello World!\n")). true. % call function in a module ?- py_call(sys:getsizeof([1,2,3]), Size). Size = 80. % call function on an attribute of a module ?- py_call(sys:path:append("/home/bob/janus")). true % get attribute from a module ?- py_call(sys:path, Path) Path = ["dir1", "dir2", ...] \end{code} Given a class in a file \verb$dog.py$ such as the following example from the Python documentation \begin{code} class Dog: tricks = [] def __init__(self, name): self.name = name def add_trick(self, trick): self.tricks.append(trick) \end{code} We can interact with this class as below. Note that \verb|$Doc| in the SWI-Prolog toplevel refers to the last toplevel binding for the variable \arg{Dog}. \begin{code} ?- py_call(dog:'Dog'("Fido"), Dog). Dog = (0x7f095c9d02e0). ?- py_call($Dog:add_trick("roll_over")). Dog = (0x7f095c9d02e0). ?- py_call($Dog:tricks, Tricks). Dog = (0x7f095c9d02e0), Tricks = ["roll_over"] \end{code} \predref{py_call}{1} can also be used to set an attribute on a module or object using the syntax \verb$py_call(Obj:Attr = Value)$. For example: \begin{code} ?- py_call(dog:'Dog'("Fido"), Dog), py_call(Dog:owner = "Bob"), py_call(Doc:owner, Owner). Dog = (0x7ffff7112170), Owner = "Bob". \end{code} If the principal term of the first argument is not \verb$Target:Func$, The argument is evaluated as the initial target, i.e., it must be an object reference or a module. For example: \begin{code} ?- py_call(dog:'Dog'("Fido"), Dog), py_call(Dog, X). Dog = X, X = (0x7fa8cbd12050). ?- py_call(sys, S). S = (0x7fa8cd582390). \end{code} \arg{Options} processed: \begin{description} \termitem{py_string_as}{+Type} If \arg{Type} is \const{atom} (default), translate a Python String into a Prolog atom. If \arg{Type} is \const{string}, translate into a Prolog string. Strings are more efficient if they are short lived. \termitem{py_object}{Boolean} If \const{true} (default \const{false}), translate the return as a Python object reference. Some objects are \textit{always} translated to Prolog, regardless of this flag. These are the Python constants \verb$None$, \verb$True$ and \verb$False$ as well as instances of the Python base classes long, float, string or tuple. Instances of sub classes of these base classes are controlled by this option. \end{description} \predicate[nondet]{py_iter}{2}{+Iterator, -Value} \nodescription \predicate[nondet]{py_iter}{3}{+Iterator, -Value, +Options} True when \arg{Value} is returned by the Python \arg{Iterator}. Python iterators may be used to implement non-deterministic foreign predicates. The implementation uses these steps: \begin{enumerate} \item Evaluate \arg{Iterator} as \predref{py_call}{2} evaluates its first argument, except the \verb$Obj:Attr = Value$ construct is not accepted. \item Call \verb$__iter__$ on the result to get the iterator itself. \item Get the \verb$__next__$ function of the iterator. \item Loop over the return values of the \textit{next} function. If the Python return value unifies with \arg{Value}, succeed with a choicepoint. Abort on Python or unification exceptions. \item Re-satisfaction continues at (4). \end{enumerate} The example below uses the built-in iterator \verb$range()$: \begin{code} ?- py_iter(range(1,3), X). X = 1 ; X = 2. \end{code} Note that the implementation performs a \textit{look ahead}, i.e., after successful unification it calls `__next__()` again. On failure the Prolog predicate succeeds deterministically. On success, the next candidate is stored. Note that a Python \textit{generator} is a Python _iterator. Therefore, given the Python generator expression below, we can use \verb$py_iter(squares(1,5),X)$ to generate the squares on backtracking. \begin{code} def squares(start, stop): for i in range(start, stop): yield i * i \end{code} \begin{arguments} \arg{Options} & is processed as with \predref{py_call}{3}. \\ \end{arguments} \begin{tags} \tag{bug} \arg{Iterator} may not depend on janus.Query() \end{tags} \predicate[semidet]{py_is_object}{1}{@Term} True when \arg{Term} is a Python object reference. Fails silently if @\arg{Term} is any other Prolog term. \begin{tags} \tag{Errors} \verb$existence_error(py_object, Term)$ is raised of \arg{Term} is a Python object, but it has been freed using \predref{py_free}{1}. \end{tags} \predicate[det]{py_free}{1}{+Obj} Immediately free (decrement the reference count) for th Python object \arg{Obj}. Further reference to \arg{Obj} using \predref{py_call}{1},2 or \predref{py_free}{1} raises an \verb$existence_error$. Note that by decrementing the reference count, we make the reference invalid from Prolog. This may not actually delete the object because the object may have references inside Python. Prolog references to Python objects are subject to atom garbage collection and thus normally do not need to be freed explicitly. \predicate[semidet]{py_with_gil}{1}{:Goal} Run \arg{Goal} as \verb$once(Goal)$ while holding the Phyton GIL (\textit{Global Interpreter Lock}). Note that \predref{py_call}{1},2 also locks the GIL. This predicate is only required if we wish to make multiple calls to Python while keeping the GIL. The GIL is a \textit{recursive} lock and thus calling \predref{py_call}{1},2 while holding the GIL does not \textit{deadlock}. \predicate[det]{py_func}{3}{+Module, +Function, -Return} \nodescription \predicate[det]{py_func}{4}{+Module, +Function, -Return, +Options} XSB compatible wrappers for \predref{py_call}{2}. Note that the wrapper supports more call patterns. \arg{Options} \begin{description} \termitem{sizecheck}{+Boolean} Used by XSB for memory management. Ignored in SWI-Prolog. \termitem{py_object}{+Boolean} Passed to \predref{py_call}{3}. \end{description} \predicate[det]{py_dot}{4}{+Module, +ObjRef, +MethAttr, -Ret} \nodescription \predicate[det]{py_dot}{5}{+Module, +ObjRef, +MethAttr, -Ret, +Options} XSB compatible wrappers for \predref{py_call}{2}. \begin{arguments} \arg{Module} & is ignored (why do we need that if we have \arg{ObjRef}?) \\ \end{arguments} \predicate[semidet]{values}{3}{+Dict, +Path, ?Val} Get the value associated with \arg{Dict} at \arg{Path}. \arg{Path} is either a single key or a list of keys. \predicate[det]{keys}{2}{+Dict, ?Keys} True when \arg{Keys} is a list of keys that appear in \arg{Dict}. \predicate[nondet]{key}{2}{+Dict, ?Key} True when \arg{Key} is a key in \arg{Dict}. Backtracking enumerates all known keys. \predicate[det]{items}{2}{+Dict, ?Items} True when \arg{Items} is a list of Key:Value that appear in \arg{Dict}. \predicate{py_shell}{0}{} Start an interactive Python REPL loop using the embedded Python interpreter. The interpreter first imports \const{janus} as below. \begin{code} from janus import * \end{code} So, we can do \begin{code} ?- py_shell. ... >>> once("writeln(X)", {"X":"Hello world"}) Hello world {'status': True} \end{code} If possible, we enable command line editing using the GNU readline library. When used in an environment where Prolog does not use the file handles 0,1,2 for the standard streams, e.g., in \verb$swipl-win$, Python's I/O is rebound to use Prolog's I/O. This includes Prolog's command line editor, resulting in a mixed history of Prolog and Pythin commands. \predicate[det]{py_pp}{1}{+Term} \nodescription \predicate[det]{py_pp}{2}{+Term, +Options} \nodescription \predicate[det]{py_pp}{3}{+Stream, +Term, +Options} Pretty prints the Prolog translation of a Python data structure in Python syntax. This exploits \verb$pformat()$ from the Python module \const{pprint} to do the actual formatting. \arg{Options} is translated into keyword arguments passed to pprint.\verb$pformat()$. For example: \begin{code} ?- py_pp(py{a:1, l:[1,2,3], size:1000000}, [underscore_numbers(true)]). {'a': 1, 'l': [1, 2, 3], 'size': 1_000_000} \end{code} \predicate[det]{py_obj_dir}{2}{+ObjRef, -List} \nodescription \predicate[det]{py_obj_dict}{2}{+ObjRef, -Dict} Examine attributes of an object. The predicate \predref{py_obj_dir}{2} fetches the names of all attributes, while \predref{py_obj_dict}{2} gets a dict with all attributes and their values. \predicate[det]{py_initialize}{3}{+Program, +Argv, +Options} Initialize and configure the embedded Python system. If this predicate is not called before any other call to Python such as \predref{py_call}{2}, it is called \textit{lazily}, passing the Prolog executable as \arg{Program}, the non-Prolog arguments as \arg{Argv} and an empty \arg{Options} list. Calling this predicate while the Python is already initialized is a no-op. This predicate is thread-safe, where the first thread initializes Python. In addition to initializing the Python system, it \begin{itemize} \item Adds the directory holding \verb$janus.py$ to the Python module search path. \item If Prolog I/O is not connected to the file handles 0,1,2, it rebinds Python I/O to use the Prolog I/O. \end{itemize} \begin{arguments} \arg{Options} & is currently ignored. It will be used to provide additional configuration options. \\ \end{arguments} \predicate[det]{py_lib_dirs}{1}{-Dirs} True when \arg{Dirs} is a list of directories searched for Python modules. The elements of \arg{Dirs} are in Prolog canonical notation. \predicate[det]{py_add_lib_dir}{1}{+Dir} \nodescription \predicate[det]{py_add_lib_dir}{2}{+Dir, +Where} Add a directory to the Python module search path. In the second form, \arg{Where} is one of \const{first} or \const{last}. \predref{py_add_lib_dir}{1} adds the directory as last. \arg{Dir} is in Prolog notation. The added directory is converted to an absolute path using the OS notation. A flexible way to add the directory holding the current Prolog file to the Python search path is in the template below. The \predref{here}{0} predicate can be replaced by any predicate defined in the file, either above or below the \predref{initializing}{1} directive. A simple name like \predref{here}{0} is good style when this code is part of a Prolog module. \begin{code} here. :- initialization ( source_file(here, File), file_directory_name(File, Dir), py_add_lib_dir(Dir, first) ). \end{code} \end{description}