SWI-Prolog Python interface
All Application Manual Name SummaryHelp

  • Documentation
    • Reference manual
    • Packages
      • SWI-Prolog Python interface
        • Introduction
        • Data conversion
        • Janus by example - Prolog calling Python
        • library(janus): Call Python from Prolog
          • py_version/0
          • py_call/1
          • py_call/2
          • py_call/3
          • py_iter/2
          • py_iter/3
          • py_setattr/3
          • py_is_object/1
          • py_is_dict/1
          • py_free/1
          • py_with_gil/1
          • py_gil_owner/1
          • py_func/3
          • py_func/4
          • py_dot/3
          • py_dot/4
          • values/3
          • keys/2
          • key/2
          • items/2
          • py_shell/0
          • py_pp/1
          • py_pp/2
          • py_pp/3
          • py_object_dir/2
          • py_object_dict/2
          • py_obj_dir/2
          • py_obj_dict/2
          • py_type/2
          • py_isinstance/2
          • py_module_exists/1
          • py_hasattr/2
          • py_import/2
          • py_module/2
          • py_initialize/3
          • py_lib_dirs/1
          • py_add_lib_dir/1
          • py_add_lib_dir/2
          • Handling Python errors in Prolog
          • Calling and data translation errors
          • Janus and virtual environments (venv)
        • Calling Prolog from Python
        • Janus and threads
        • Janus and signals
        • Janus versions
        • Janus as a Python package
        • Prolog and Python
        • Janus performance evaluation
        • Python or C/C++ for accessing resources?
        • Janus platforms notes
        • Compatibility to the XSB Janus implementation
        • Status of Janus

4 library(janus): Call Python from Prolog

This library implements calling Python from Prolog. It is available directly from Prolog if the janus package is bundled. The library provides access to an embedded Python instance. If SWI-Prolog is embedded into Python using the Python package janus-swi, this library is provided either from Prolog or from the Python package.

Normally, the Prolog user can simply start calling Python using py_call/2 or friends. In special cases it may be needed to initialize Python with options using py_initialize/3 and optionally the Python search path may be extended using py_add_lib_dir/1.

[det]py_version
Print version info on the embedded Python installation based on Python sys.version. If a Python virtual environment (venv) is active, indicate this with the location of this environment found.
[det]py_call(+Call)
[det]py_call(+Call, -Return)
[det]py_call(+Call, -Return, +Options)
Call Python and return the result of the called function. Call has the shape‘[Target][:Action]*`, where Target is either a Python module name or a Python object reference. Each Action is either an atom to get the denoted attribute from current 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. Action without a Target denotes a buit-in function.

Arguments to Python functions use the Python conventions. Both positional and keyword arguments are supported. Keyword arguments are written as Name = Value and must appear after the positional arguments.

Below are some examples.

% 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", ...]

Given a class in a file dog.py such as the following example from the Python documentation

class Dog:
    tricks = []

    def __init__(self, name):
        self.name = name

    def add_trick(self, trick):
        self.tricks.append(trick)

We can interact with this class as below. Note that $Doc in the SWI-Prolog toplevel refers to the last toplevel binding for the variable Dog.

?- py_call(dog:'Dog'("Fido"), Dog).
Dog = <py_Dog>(0x7f095c9d02e0).

?- py_call($Dog:add_trick("roll_over")).
Dog = <py_Dog>(0x7f095c9d02e0).

?- py_call($Dog:tricks, Tricks).
Dog = <py_Dog>(0x7f095c9d02e0),
Tricks = ["roll_over"]

If the principal term of the first argument is not Target:Func, The argument is evaluated as the initial target, i.e., it must be an object reference or a module. For example:

?- py_call(dog:'Dog'("Fido"), Dog),
   py_call(Dog, X).
   Dog = X, X = <py_Dog>(0x7fa8cbd12050).
?- py_call(sys, S).
   S = <py_module>(0x7fa8cd582390).

Options processed:

py_object(Boolean)
If true (default false), translate the return as a Python object reference. Some objects are always translated to Prolog, regardless of this flag. These are the Python constants None, True and False as well as instances of the Python base classes int, float, str or tuple. Instances of sub classes of these base classes are controlled by this option.
py_string_as(+Type)
If Type is atom (default), translate a Python String into a Prolog atom. If Type is string, translate into a Prolog string. Strings are more efficient if they are short lived.
py_dict_as(+Type)
One of dict (default) to map a Python dict to a SWI-Prolog dict if all keys can be represented. If {} or not all keys can be represented, Return is unified to a term {k:v, ...} or py({}) if the Python dict is empty.
Compatibility
PIP. The options py_string_as and py_dict_as are SWI-Prolog specific, where SWI-Prolog Janus represents Python strings as atoms as required by the PIP and it represents Python dicts by default as SWI-Prolog dicts. The predicates values/3, keys/2, etc. provide portable access to the data in the dict.
[nondet]py_iter(+Iterator, -Value)
[nondet]py_iter(+Iterator, -Value, +Options)
True when Value is returned by the Python Iterator. Python iterators may be used to implement non-deterministic foreign predicates. The implementation uses these steps:

  1. Evaluate Iterator as py_call/2 evaluates its first argument, except the Obj:Attr = Value construct is not accepted.
  2. Call __iter__ on the result to get the iterator itself.
  3. Get the __next__ function of the iterator.
  4. Loop over the return values of the next function. If the Python return value unifies with Value, succeed with a choicepoint. Abort on Python or unification exceptions.
  5. Re-satisfaction continues at (4).

The example below uses the built-in iterator range():

?- py_iter(range(1,3), X).
X = 1 ;
X = 2.

Note that the implementation performs a 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 generator is a Python iterator. Therefore, given the Python generator expression below, we can use py_iter(squares(1,5),X) to generate the squares on backtracking.

def squares(start, stop):
     for i in range(start, stop):
         yield i * i
Options is processed as with py_call/3.
Compatibility
PIP. The same remarks as for py_call/2 apply.
bug
Iterator may not depend on janus.query(), i.e., it is not possible to iterate over a Python iterator that under the hoods relies on a Prolog non-deterministic predicate.
[det]py_setattr(+Target, +Name, +Value)
Set a Python attribute on an object. If Target is an atom, it is interpreted as a module. Otherwise it is normally an object reference. py_setattr/3 allows for chaining and behaves as if defined as
py_setattr(Target, Name, Value) :-
    py_call(Target, Obj, [py_object(true)]),
    py_call(setattr(Obj, Name, Value)).
Compatibility
PIP
[semidet]py_is_object(@Term)
True when Term is a Python object reference. Fails silently if Term is any other Prolog term.
Errors
existence_error(py_object, Term) is raised of Term is a Python object, but it has been freed using py_free/1.
Compatibility
PIP. The SWI-Prolog implementation is safe in the sense that an arbitrary term cannot be confused with a Python object and a reliable error is generated if the references has been freed. Portable applications can not rely on this.
[semidet]py_is_dict(@Term)
True if Term is a Prolog term that represents a Python dict.
Compatibility
PIP. The SWI-Prolog version accepts both a SWI-Prolog dict and the {k:v,...} representation. See py_dict_as option of py_call/2.
[det]py_free(+Obj)
Immediately free (decrement the reference count) for the Python object Obj. Further reference to Obj using e.g., py_call/2 or py_free/1 raises an 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.

Compatibility
PIP. The SWI-Prolog implementation is safe and normally reclaiming Python object can be left to the garbage collector. Portable applications may not assume garbage collection of Python objects and must ensure to call py_free/1 exactly once on any Python object reference. Not calling py_free/1 leaks the Python object. Calling it twice may lead to undefined behavior.
[semidet]py_with_gil(:Goal)
Run Goal as once(Goal) while holding the Phyton GIL (Global Interpreter Lock). Note that all predicates that interact with Python lock the GIL. This predicate is only required if we wish to make multiple calls to Python while keeping the GIL. The GIL is a recursive lock and thus calling py_call/1,2 while holding the GIL does not deadlock.
[semidet]py_gil_owner(-Thread)
True when the Python GIL is owned by Thread. Note that, unless Thread is the calling thread, this merely samples the current state and may thus no longer be true when the predicate succeeds. This predicate is intended to help diagnose deadlock problems.

Note that this predicate returns the Prolog threads that locked the GIL. It is however possible that Python releases the GIL, for example if it performs a blocking call. In this scenario, some other thread or no thread may hold the gil.

[det]py_func(+Module, +Function, -Return)
[det]py_func(+Module, +Function, -Return, +Options)
Call Python Function in Module. The SWI-Prolog implementation is equivalent to py_call(Module:Function, Return). See py_call/2 for details.
Compatibility
PIP. See py_call/2 for notes. Note that, as this implementation is based on py_call/2, Function can use chaining, e.g., py_func(sys, path:append(dir), Return) is accepted by this implementation, but not portable.
[det]py_dot(+ObjRef, +MethAttr, -Ret)
[det]py_dot(+ObjRef, +MethAttr, -Ret, +Options)
Call a method or access an attribute on the object ObjRef. The SWI-Prolog implementation is equivalent to py_call(ObjRef:MethAttr, Return). See py_call/2 for details.
Compatibility
PIP. See py_func/3 for details.
[semidet]values(+Dict, +Path, ?Val)
Get the value associated with Dict at Path. Path is either a single key or a list of keys.
Compatibility
PIP. Note that this predicate handle a SWI-Prolog dict, a {k:v, ...} term as well as py({k:v, ...}.
[det]keys(+Dict, ?Keys)
True when Keys is a list of keys that appear in Dict.
Compatibility
PIP. Note that this predicate handle a SWI-Prolog dict, a {k:v, ...} term as well as py({k:v, ...}.
[nondet]key(+Dict, ?Key)
True when Key is a key in Dict. Backtracking enumerates all known keys.
Compatibility
PIP. Note that this predicate handle a SWI-Prolog dict, a {k:v, ...} term as well as py({k:v, ...}.
[det]items(+Dict, ?Items)
True when Items is a list of Key:Value that appear in Dict.
Compatibility
PIP. Note that this predicate handle a SWI-Prolog dict, a {k:v, ...} term as well as py({k:v, ...}.
py_shell
Start an interactive Python REPL loop using the embedded Python interpreter. The interpreter first imports janus as below.
from janus import *

So, we can do

?- py_shell.
...
>>> query_once("writeln(X)", {"X":"Hello world"})
Hello world
{'truth': True}

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 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.

[det]py_pp(+Term)
[det]py_pp(+Term, +Options)
[det]py_pp(+Stream, +Term, +Options)
Pretty prints the Prolog translation of a Python data structure in Python syntax. This exploits pformat() from the Python module pprint to do the actual formatting. Options is translated into keyword arguments passed to pprint.pformat(). In addition, the option nl(Bool) is processed. When true (default), we use pprint.pp(), which makes the output followed by a newline. For example:
?- py_pp(py{a:1, l:[1,2,3], size:1000000},
         [underscore_numbers(true)]).
{'a': 1, 'l': [1, 2, 3], 'size': 1_000_000}
Compatibility
PIP
[det]py_object_dir(+ObjRef, -List)
[det]py_object_dict(+ObjRef, -Dict)
Examine attributes of an object. The predicate py_object_dir/2 fetches the names of all attributes, while py_object_dir/2 gets a dict with all attributes and their values.
Compatibility
PIP
[det]py_obj_dir(+ObjRef, -List)
[det]py_obj_dict(+ObjRef, -Dict)
deprecated
Use py_object_dir/2 or py_object_dict/2.
[det]py_type(+ObjRef, -Type:atom)
True when Type is the name of the type of ObjRef. This is the same as type(ObjRef).__name__ in Python.
Compatibility
PIP
[semidet]py_isinstance(+ObjRef, +Type)
True if ObjRef is an instance of Type or an instance of one of the sub types of Type. This is the same as isinstance(ObjRef) in Python.
Type is either a term Module:Type or a plain atom to refer to a built-in type.
Compatibility
PIP
[semidet]py_module_exists(+Module)
True if Module is a currently loaded Python module or it can be loaded.
Compatibility
PIP
[nondet]py_hasattr(+ModuleOrObj, ?Name)
True when Name is an attribute of Module. The name is derived from the Python built-in hasattr(). If Name is unbound, this enumerates the members of py_object_dir/2.
ModuleOrObj If this is an atom it refers to a module, otherwise it must be a Python object reference.
Compatibility
PIP
[det]py_import(+Spec, +Options)
Import a Python module. Janus imports modules automatically when referred in py_call/2 and related predicates. Importing a module implies the module is loaded using Python's __import__() built-in and added to a table that maps Prolog atoms to imported modules. This predicate explicitly imports a module and allows it to be associated with a different name. This is useful for loading nested modules, i.e., a specific module from a Python package as well as for avoiding conflicts. For example, with the Python selenium package installed, we can do in Python:
>>> from selenium import webdriver
>>> browser = webdriver.Chrome()

Without this predicate, we can do

?- py_call('selenium.webdriver':'Chrome'(), Chrome).

For a single call this is fine, but for making multiple calls it gets cumbersome. With this predicate we can write this.

?- py_import('selenium.webdriver', []).
?- py_call(webdriver:'Chrome'(), Chrome).

By default, the imported module is associated to an atom created from the last segment of the dotted name. Below we use an explicit name.

?- py_import('selenium.webdriver', [as(browser)]).
?- py_call(browser:'Chrome'(), Chrome).
Errors
permission_error(import_as, py_module, As) if there is already a module associated with As.
[det]py_module(+Module:atom, +Source:string)
Load Source into the Python module Module. This is intended to be used together with the string quasi quotation that supports long strings in SWI-Prolog. For example:
:- use_module(library(strings)).
:- py_module(hello,
             {|string||
              | def say_hello_to(s):
              |     print(f"hello {s}")
              |}).

Calling this predicate multiple times with the same Module and Source is a no-op. Called with a different source creates a new Python module that replaces the old in the global namespace.

Errors
python_error(Type, Data) is raised if Python raises an error.
[det]py_initialize(+Program, +Argv, +Options)
Initialize and configure the embedded Python system. If this predicate is not called before any other call to Python such as py_call/2, it is called lazily, passing the Prolog executable as Program, passing Argv from the Prolog flag py_argv and an empty Options list.

Calling this predicate while the Python is already initialized is a no-op. This predicate is thread-safe, where the first call initializes Python.

In addition to initializing the Python system, it

  • Adds the directory holding janus.py to the Python module search path.
  • 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.
Options is currently ignored. It will be used to provide additional configuration options.
[det]py_lib_dirs(-Dirs)
True when Dirs is a list of directories searched for Python modules. The elements of Dirs are in Prolog canonical notation.
Compatibility
PIP
[det]py_add_lib_dir(+Dir)
[det]py_add_lib_dir(+Dir, +Where)
Add a directory to the Python module search path. In the second form, Where is one of first or last. py_add_lib_dir/1 adds the directory as last. The property sys:path is not modified if it already contains Dir.

Dir is in Prolog notation. The added directory is converted to an absolute path using the OS notation using prolog_to_os_filename/2.

If Dir is a relative path, it is taken relative to Prolog source file when used as a directive and relative to the process working directory when called as a predicate.

Compatibility
PIP. Note that SWI-Prolog uses POSIX file conventions internally, mapping to OS conventions inside the predicates that deal with files or explicitly using prolog_to_os_filename/2. Other systems may use the native file conventions in Prolog.

4.1 Handling Python errors in Prolog

If py_call/2 or one of the other predicates that access Python causes Python to raise an exception, this exception is translated into a Prolog exception of the shape below. The library defines a rule for print_message/2 to render these errors in a human readable way.

error(python_error(ErrorType, Value), _)

Here, ErrorType is the name of the error type, as an atom, e.g., ’TypeError’. Value is the exception object represented by a Python object reference. The library(janus) defines the message formatting, which makes us end up with a message like below.

?- py_call(nomodule:noattr).
ERROR: Python 'ModuleNotFoundError':
ERROR:   No module named 'nomodule'
ERROR: In:
ERROR:   [10] janus:py_call(nomodule:noattr)

The Python stack trace is handed embedded into the second argument of the error(Formal, ImplementationDefined). If an exception is printed, printing the Python backtrace, is controlled by the Prolog flags py_backtrace (default true) and py_backtrace_depth (default 4).

Compatibility
PIP. The embedding of the Python backtrace is SWI-Prolog specific.

4.2 Calling and data translation errors

Errors may occur when converting Prolog terms to Python objects as defined in section 2. These errors are reported as instantiation_error, type_error(Type, Culprit) or domain_error(Domain, Culprit).

Defined domains are:

py_constant
In a term @(Constant), Constant is not true, false or none. For example, py_call(print(@error)).
py_keyword_arg
In a call to Python, a non keyword argument follows a keyword argument. For example, py_call(m:f(1,x=2,3), R)
py_string_as
The value for a py_string_as(As) option is invalid. For example, py_call(m:f(), R, [py_string_as(float)])
py_dict_as
The value for a py_dict_as(As) option is invalid. For example, py_call(m:f(), R, [py_dict_as(list)])
py_term
A term being translated to Python is unsupported. For example, py_call(m:f(point(1,2)), R).

Defined types are:

py_object
A Python object reference was expected. For example, py_free(42)
rational
A Python fraction instance is converted to a Prolog rational number, but the textual conversion does not produce a valid rational number. This can happen if the Python fraction is subclassed and the __str__() method does not produce a correct string.
py_key_value
Inside a {k:v, ...} representation for a dictionary we find a term that is not a key-value pair. For example, py_call(m:f({a:1, x}), R)
py_set
Inside a py_set(Elements), Elements is not a list. For example, py_call(m:f(py_set(42)), R).
py_target
In py_call(Target:FuncOrAttrOrMethod), Target is not a module (atom) or Python object reference. For example, py_call(7:f(), R).
py_callable
In py_call(Target:FuncOrAttrOrMethod), FuncOrAttrOrMethod is not an atom or compound. For example, py_call(m:7, R).

4.3 Janus and virtual environments (venv)

An embedded Python system does not automatically pick up Python virtual environments. It is supposed to setup its own environment. Janus is sensitive to Python venv environments. Running under such as environment is assumed if the environment variable VIRTUAL_ENV points at a directory that holds a file pyvenv.cfg. If the virtual environment is detected, the actions in the list below are taken.3This is based on observing how Python 3.10 on Linux responds to being used inside a virtual environment. We do not know whether this covers all platforms and versions.

  • Initialize Python using the -I flag to indicate isolation.
  • Set sys.prefix to the value of the VIRTUAL_ENV environment variable.
  • Remove all directories with base name site-packages or dist-packages from sys.path.4Note that -I only removes the personal packages directory, while the Python executable removes all, so we do the same.
  • Add $VIRTUAL_ENV/lib/pythonX.Y/site-packages to sys.path, where X and Y are the major and minor version numbers of the embedded Python library. If this directory does not exist we print a diagnostic warning.
  • Add a message to py_version/0 that indicates we are using a virtual environment and from which directory.