The API is being developed in close cooperation with the XSB team and aims to provide a de-facto standard interface between Python and Prolog.
Python has a huge developer community that maintains a large set of resources, notably interfaces to just about anything one can imagine. Making such interfaces directly available to Prolog can surely be done. However, developing an interface typically requires programming in C or C++, a skill that is not widely available everywhere. Being able to access Python effortlessly from Prolog puts us in a much better position because Python experience is widely available in our target audience. This solution was proposed in Andersen & Swift, 2023, Swift & Andersen, 2023, initially developed for XSB.
Janus provides a bi-directional interface between Prolog and Python
using the low-level C API of both languages. This makes using Python
from Prolog as simple as taking the standard SWI-Prolog distribution and
loading library(janus)
. Using Prolog from Python is as
simple as
import janus_swi as janus
and start making calls. Both
Prolog and Python being dynamically typed languages, we can define an
easy to use interface that provides a latency of about one μS.
The Python interface is modeled after the recent JavaScript interface developed for the WASM (Web Assembly) version. That is
The bi-directional conversion between Prolog and Python terms is
summarized in the table below. For compatibility with Prolog
implementations without native dicts we support converting the
{k1:v1, k2:v2, ...}
to dicts. Note that {k1:v1, k2:v2}
is syntactic sugar for {}(','(:(k1,v1), :(k2,v2)))
. We
allow for embedding this in a py(Term)
such that, with py
defined as prefix operator, py{k1:v1, k2:v2}
is
both valid syntax as SWI-Prolog dict as as ISO Prolog compliant term and
both are translated into the same Python dict. Note that {}
translates to a Python string, while py({})
translates into
an empty Python dict.
By default we translate Python strings into Prolog atoms. Given we
support strings, this is somewhat dubious. There are two reasons for
this choice. One is the pragmatic reason that Python uses strings both
for identifiers and arbitrary text. Ideally we'd have the first
translated to Prolog atoms and the latter to Prolog strings, but,
because we do not know which strings act as identifier and which as just
text, this is not possible. The second is to improve compatibility with
Prolog systems that do not support strings. Note that py_call/3
and py_iter/3
provide the option
py_string_as(string)
to obtain a string if this is
desirable.
Prolog | Python | Notes | |
Variable | ⟶ | - | (instantiation error) |
Integer | ⟺ | int | Supports big integers |
Rational | ⟺ | fractions.Fraction() | |
Float | ⟺ | float | |
@(none) | ⟺ | None | |
@(true) | ⟺ | True | |
@(false) | ⟺ | False | |
Atom | ⟵ | enum.Enum() | Name of Enum instance |
Atom | ⟷ | String | Except the above reserved three atoms |
String | ⟶ | String | |
#(Term) | ⟶ | String | stringify using write_canonical/1 if not atomic |
prolog(Term) | ⟶ | janus.Term() | Represent any Prolog term |
Term | ⟵ | janus.Term() | |
List | ⟶ | List | |
List | ⟵ | Sequence | |
List | ⟵ | Iterator | Note that a Generator is an Iterator |
py_set(List) | ⟺ | Set | |
-(a,b, ... ) | ⟺ | (a,b, ... ) | Python Tuples |
Dict | ⟺ | Dict | |
{k:v, ...} | ⟹ | Dict | Compatibility (see above) |
py({k:v, ...}) | ⟹ | Dict | Compatibility (see above) |
eval(Term) | ⟹ | Object | Evaluate Term as first argument of py_call/2 |
py_obj blob | ⟺ | Object | Used for any Python object not above |
Compound | ⟶ | - | for any term not above (type error) |
The interface supports unbounded integers and rational numbers. Large integers (> 64 bits) are converted using a hexadecimal string as intermediate. SWI-Prolog rational numbers are mapped to the Python class fractions:Fraction. Currently the mapping rational numbers uses an intermediate decimal string and is therefore relatively slow. Mapping from Python to Prolog relies on the ((_)_str__)() method of the instance returning +/-<num>/<den> where <num> and <den> are decimal numbers.
The conversion #(Term) allows passing anything as a Python string. If
Term is an atom or string, this is the same as passing the
atom or string. Any other Prolog term is converted as defined by
write_canonical/1.
The conversion prolog(Term)
creates an instance of janus.Term().
This class encapsulates a copy of an arbitrary Prolog term. The
SWI-Prolog implementation uses the
PL_record() and PL_recorded() functions to store and
retrieve the term. Internally, janus.Term()
is used to represent Prolog exeptions that are raised during the
execution of
janus.once() or janus.Query().
Python Tuples are array-like objects and thus map best to a Prolog
compound term. There are two problems with this. One is that few systems
support compound terms with arity zero, e.g., f
and many
systems have a limit on the arity of compound terms. Using
Prolog comma lists, e.g., (a,b,c)
does not
implement array semantics, cannot represent empty tuples and cannot
disambiguate tuples with one element from the element itself. We settled
with compound terms using the
as functor to
make the common binary tuple map to a Prolog pair.
-
This section introduces Janus calling Python from Prolog by examples.
The spaCy package provides natural language processing. This section illustrates the Janus library using spaCy. Typically, spaCy and the English language models may be installed using
> pip install spacy > python -m spacy download en
After spaCy is installed, we can define model/1 to represent a Python object for the English language model using the code below. Note that by tabling this code as shared, the model is loaded only once and is accessible from multiple Prolog threads.
:- table english/1 as shared. english(NLP) :- py_call(spacy:load(en_core_web_sm), NLP).
Calling english(X)
results in X =
<py_English>(0x7f703c24f430)
. This object implements
the Python callable protocol, i.e., it behaves as a function
with additional properties and methods. Calling the model with a string
results in a parsed document. We can use this from Prolog using the
built-in __call__
method:
?- english(NLP), py_call(NLP:'__call__'("This is a sentence."), Doc). NLP = <py_English>(0x7f703851b8e0), Doc = [<py_Token>(0x7f70375be9d0), <py_Token>(0x7f70375be930), <py_Token>(0x7f70387f8860), <py_Token>(0x7f70376dde40), <py_Token>(0x7f70376de200) ].
This is not what we want. Because the spaCy Doc
class
implements the sequence protocol it is translated into a Prolog
list of spaCy Token
instances. The Doc
class
implements many more methods that we may wish to use. An example is
noun_chunks
, which provides a Python generator
that enumerates the noun chunks found in the input. Each chunk is an
instance of Span
, a sequence of Token
instances that have the property text
. So, if we want the
noun chunks as text, we can write the following program:
:- use_module(library(janus)). :- table english/1. english(NLP) :- py_call(spacy:load(en_core_web_sm),NLP). noun(Sentence, Noun) :- english(NLP), py_call(NLP:'__call__'(Sentence), Doc, [py_object(true)]), py_iter(Doc:noun_chunks, Span, [py_object]), py_call(Span:text, Noun).
After which we can call
?- noun("This is a sentence.", Noun). Noun = 'This' ; Noun = 'a sentence'.
This library implements calling Python from Prolog. It is available
directly from Prolog if the janus package is bundled, providing 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.
sys:version
.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"]
py_call/1 can also be used to
set an attribute on a module or object using the syntax py_call(Obj:Attr = Value)
.
For example:
?- py_call(dog:'Dog'("Fido"), Dog), py_call(Dog:owner = "Bob"), py_call(Doc:owner, Owner). Dog = <py_Dog>(0x7ffff7112170), Owner = "Bob".
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:
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.
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 long, float, string or tuple.
Instances of sub classes of these base classes are controlled by this
option.
Obj:Attr = Value
construct is not accepted.
__iter__
on the result to get the iterator itself.
__next__
function of the iterator.
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. |
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.
once(Goal)
while holding the Phyton
GIL (Global Interpreter Lock). Note that 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 recursive
lock and thus calling py_call/1,2
while holding the GIL does not deadlock.Module | is ignored (why do we need that if we have ObjRef?) |
janus
as below.
from janus import *
So, we can do
?- py_shell. ... >>> once("writeln(X)", {"X":"Hello world"}) Hello world {'status': 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.
pformat()
from the Python
module
pprint
to do the actual formatting. Options is
translated into keyword arguments passed to pprint.pformat()
.
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}
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
janus.py
to the Python
module search path.
Options | is currently ignored. It will be used to provide additional configuration options. |
first
or last
. py_add_lib_dir/1
adds the directory as last.
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 here/0 predicate can be replaced by any predicate defined in the file, either above or below the initializing/1 directive. A simple name like here/0 is good style when this code is part of a Prolog module.
here. :- initialization ( source_file(here, File), file_directory_name(File, Dir), py_add_lib_dir(Dir, first) ).
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, Stack)
, _)
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. Stack is either @none
or an object that captures the Python stack. 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 binding can also call Prolog from Python. This can both be used to realize call backs, i.e., the Python system embedded into Prolog calls Prolog, or after embedding SWI-Prolog into Python.
Loading janus into Python is realized using the Python package
janus-swi
, which defines the module janus_swi
.
We do not call this simply janus
to allow coexistence of
janus for multiple Prolog implementations. Unless you plan to interact
with multiple Prolog systems in the same session, we advice to import
janus for SWI-Prolog as below.
import janus_swi as janus
If Python is embedded into SWI-Prolog, the Python module may be
imported both as janus
and janus_swi
. Using
janus
allows the same Python code to be used from different
Prolog systems, while using janus_swi
allows the same code
to be used both for embedding Python into Prolog and Prolog into Python.
In the remainder of this section we consider the module to be named
janus
.
The Python module janus
provides utility functions and
defines the classes janus.Query(), janus.Term()
and
janus.PrologError(). We
start our discussion by introducing the janus.once(query,inputs)
function for calling Prolog goals as once/1.
A Prolog goal is constructed from a string and a dict with input
bindings and returns output bindings as a dict. For
example
>>> import janus_swi as janus >>> janus.once("Y is X+1", {"X":1}) {'Y': 2, 'status': True}
Note that the input argument may also be passed literally. Below we give two examples. We strongly advise against using string interpolation for three reasons. Firstly, the query strings are compiled and cached on the Prolog sided and (thus) we assume a finite number of distinct query strings. Secondly, string interpolation is sensitive to injection attacks. Notably inserting quoted strings can easily be misused to create malicious queries. Thirdly and finally, serializing and deserializing the data is generally slower then using the input dictionary, especially if the data is large. Using a dict for input and output together with a (short) string to denote the goal is easy to use and fast.
>>> janus.once("Y is 1+1", {}) # Ok for "static" queries {'Y': 2, 'status': True} >>> x = 1 >>> janus.once(f"Y is {x}+1", {}) # Do not use this {'Y': 2, 'status': True} # See above
The output dict contains all named Prolog variables that (1) are not in the input dict and (2) do not start with an underscore. For example, to get the grandparents of a person given parent/2 relations we can use the code below, where the _GP and _P do not appear in the output dict. This both saves time and avoids the need to convert Prolog data structures that cannot be represented in Python such as variables or arbitrary compound terms.
>>> janus.once("findall(_GP, parent(Me, _P), parent(_P, _GP), GPs)", {'Me':'Jan'})["GPs"] [ 'Kees', 'Jan' ]
In addition to the variable bindings the dict contains a key
status
1Note that
variable bindings always start with an uppercase latter.
that represents the truth value of evaluating the query. In normal
Prolog this is a Python Boolean. In systems that implement Well
Founded Semantics, this may also be the string ’Undefined'
.
If evaluation of the query failed, all variable bindings are bound to
the Python constant None
and the status
key is False
.
The following Python function returns True
if the Prolog
system supports unbounded integers and False
otherwise.
def hasBigIntegers(): janus.once("current_prolog_flag(bounded,false)")['status']
While janus.once() deals
with semi-deterministic goals, the class janus.Query()
implements a Python iterator that iterates over the solutions
of a Prolog goal. The iterator may be aborted using the Python break
statement. As with
janus.once(), the returned dict
contains a status
field. This field cannot be False
though and thus is either
True
or the string 'Undefined'
.2The
representation of Undefined is still under discussion.
import janus_swi as janus def printRange(from, to): for d in janus.Query("between(F,T,X)", {"F":from, "T":to}) print(d["X"])
Iterators may be nested. For example, we can create a list of tuples like below.
def double_iter(w,h): tuples=[] for yd in janus.Query("between(1,M,Y)", {"M":h}): for xd in janus.Query("between(1,M,X)", {"M":w}): tuples.append((xd['X'],yd['Y'])) return tuples
After this, we may run
>>> demo.double_iter(2,3) [(1, 1), (2, 1), (1, 2), (2, 2), (1, 3), (2, 3)]
In addition to the iterator protocol that class janus.Query() implements, it also implements the methods janus.Query.next() and janus.Query.close(). This allows for e.g.
q = Query("between(1,3,X)") while ( s := q.next() ): print(s['X']) q.close()
But, iterators based on Prolog goals are fragile. This is because, while it is possible to open and run a new query while there is an open query, the inner query must be closed before we can ask for the next solution of the outer query. We illustrate this using the sequence below.
>>> q1 = Query("between(1,3,X)") >>> q2 = Query("between(1,3,X)") >>> q2.next() {'status': True, 'X': 1} >>> q1.next() Traceback (most recent call last): ... swipl.Error: swipl.next_solution(): not inner query >>> q2.close() >>> q1.next() {'status': True, 'X': 1} >>> q1.close()
Failure to close a query typically leaves SWI-Prolog in an inconsistent state and further interaction with Prolog is likely to crash the process. Future versions may improve on that.
True
, such
changes are preserved.
>>> once("b_setval(a, 1)", keep=True) {'status': 'True'} >>> once("b_getval(a, X)") {'status': 'True', 'X': 1}
If query fails, the variables of the query are bound to
the Python constant None
. The bindings object
includes a key
status
3As this name
is not a valid Prolog variable name, this cannot be ambiguous.
that has the value False
(query failed, all bindings are None
), True
(query succeeded, variables are bound to the result converting Prolog
data to Python) or
'Undefined'
, a Python string that indicates the answer is
undefined according to the Well Founded Semantics. See e.g.,
undefined/0.
For example
>>> import janus_swi as janus >>> janus.once("undefined") {'status': 'Undefined'}
None
and the text is read from file. If data
is a string, it provides the Prolog text that is loaded and file
is used as identifier for source locations and error messages.
The module argument denotes the target module. That is where
the clauses are added to if the Prolog text does not define a module or
where the exported predicates of the module are imported into.
If data is not provided and file is not accessible this raises a Prolog exception. Errors that occur during the compilation are printed using print_message/2 and can currently not be captured easily. The script below prints the train connections as a list of Python tuples.
import janus_swi as janus janus.consult("trains", """ train('Amsterdam', 'Haarlem'). train('Amsterdam', 'Schiphol'). """) print([d['Tuple'] for d in janus.Query("train(_From,_To),Tuple=_From-_To")])
Class janus.Query() is similar to the janus.once() function, but it returns a Python iterator that allows for iterating over the answers to a non-deterministic Prolog predicate.
status
False
.
See discussion above.|
None janus.Query.next()Query
as an iterator is to be preferred. See discussion
above.Class janus.Term() encapsulates a Prolog term. Similarly to the Python object reference (see py_is_object/1), the class allows Python to represent arbitrary Prolog data, typically with the intend to pass it back to Prolog.
prolog(Term)
tho the data
conversion processes. As a result, we can do
?- py_call(janus:echo(prolog(hello(world))), Obj, [py_object(true)]). Obj = <py_Term>(0x7f7a14512050). ?- py_call(print($Obj)). hello(world) Obj = <py_Term>(0x7f7a14512050).
Class janus.PrologError(), derived from the Python class Exception represents a Prolog exception that typically results from calling janus.once() or using janus.Query(). The class either encapsulates a string on a Prolog exception term using janus.Term. Prolog exceptions are used to represent errors raised by Prolog. Strings are used to represent errors from invalid use of the interface. The default behavior gives the expected message:
>>> x = janus.once("X is 3.14/0")['X'] Traceback (most recent call last): ... janus.PrologError: //2: Arithmetic: evaluation error: `zero_divisor'
At this moment we only define a single Python class for representing Prolog exceptions. This suffices for error reporting, but does not make it easy to distinguish different Prolog errors. Future versions may improve on that by either subclassing janus.PrologError or provide a method to classify the error more easily.
Where SWI-Prolog support native preemptively scheduled threads that exploit multiple cores, Python has a single interpreter that can switch between native threads.4Actually, you can create multiple Python interpreters. It is not yet clear to us whether that can help improving on concurrency. Initially the Python interpreter is associated with the thread that created it which, for janus, is the first thread calling Python. Janus uses PyGILState_Ensure() and PyGILState_Release() around calls to e.g. py_call/2. In addition, the thread that created Python releases its interpreter after every call from Prolog on Python. As a result:
The Janus
GIT repo provides setup.py
. Janus may be installed as a
Python package after downloading using
pip install .
pip allows for installation from the git repository in a one-liner as below.
pip install git+https://github.com/SWI-Prolog/packages-swipy.git#egg=janus_swi
Installing janus as a Python package requires
setup.py
runs swipl --dump-runtime-variables
to obtain the installation locations of the various Prolog components.
On Windows, if swipl is not on %PATH%
, setup.py
tries the registry to find the default binary installation.
After successful installation we should be able to use Prolog directly from Python. For example:
python >>> from janus_swi import * >>> once("writeln('Hello world!')") Hello world! {'status': True} >>> [a["D"] for a in Query("between(1,6,D)")] [1, 2, 3, 4, 5, 6] >>> prolog() ?- version. Welcome to SWI-Prolog (threaded, 64 bits, version 9.1.12-8-g70b70a968-DIRTY) SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software. ... ?-
Prolog is a very different language than imperative languages. An interesting similarity is the notion of backtracking vs. Python iterators.
Below is a table to give some feeling on the overhead of making calls between Prolog and Python. These figures are roughly the same as the figures for the XSB/Python interface. All benchmarks have been executed on AMD3950X running Ubuntu 22.04, SWI-Prolog 9.1.11 and Python 3.10.6.
Action | Time (seconds) |
Echo list with 1,000,000 elements | 0.12 |
Call Pyton demo:int() from Prolog 1,000,000 times | 0.44 |
Call Pyton demo:sumlist3(5,[1,2,3]) from Prolog
1,000,000 times | 1.4 |
Call Prolog Y is X+1 from Python 1,000,000 times | 1.9 |
Iterate from Python over Prolog goal between(1, 1 000 000,
X) | 1.1 |
Iterate over Python iterator range(1,1000000) from
Prolog | 0.17 |
Using Python as an intermediate to access external resources allows writing such interfaces with less effort by a much wider community. The resulting interface is often also more robust due to well defined data conversion and sound memory management that you get for free.
Nevertheless, Python often accesses resources with a C or C++ API. We can also create this bridge directly, bypassing Python. That avoids one layer of data conversion and preserves the excellent multi-threading capabilities of SWI-Prolog. As is, Python operations are synchronized using the Python GIL, a global lock that allows for only a single thread to use Python at the same time.5There are rumors that Python's multi threading will be able to use multiple cores.
Writing an interface for SWI-Prolog is typically easier that for
Python/C because memory management is easier. Where we need to manage
reference counts to Python objects through all possibly paths of the C
functions, SWI-Prolog term_t
merely has to be allocated
once in the function. All failure parts will discard the Prolog data
automatically through backtracking and all success paths will do so
through the Prolog garbage collector.6Using
a Python C++ interface such as pybind11
simplifies memory management for a Python interface.
Summarizing, the presented interface is ideal to get started quickly. Applications that need to access C/C++ resources and need either exploit all cores of your hardware or get the best performance on calls or exchanging data should consider using the C or C++ interfaces of SWI-Prolog.
Janus relies on the C APIs of Prolog and Python and functions therefore independent from the platform. While the C, Python and Prolog code the builds Janus is platform independent, dynamically loading Prolog into Python or Python into Prolog depends on versions as well as several properties of the dynamic linking performed by the platform. In the sections below we describe some of the issues.
We tested the Windows platform using SWI-Prolog binaries from
https://www.swi-prolog.org/Downloads.html
and Python downloaded from
https://www.python.org/downloads/windows/.
The SWI-Prolog binary provides janus.dll
which is linked to
python3.dll
, a “stable API'' based wrapper that each
Python 3 binary distribution provides in addition to python3xx.dll
.
Calling Python from Prolog is supported out of the box, provided the
folder holding
python3.dll
is in the search %PATH%
.
The Python package can be installed using pip as described in
section 7. Once built, this package
finds SWI-Prolog on %PATH%
or using the registry and should
be fairly independent from the Prolog version as long as it is version
9.1.12 or later.
On Linux systems we bind to the currently installed Prolog and Python version. This should work smoothly from source. Janus is included in the PPA distribution for Ubuntu as well as in the Docker images. It is currently not part of the SNAP distribution.
See section 7 for for building the janus_swi
Python package.
Unfortunately MacOS versions of Python do not ship with the
equivalent of python3.dll
found on Windows. This implies we
can only compile our binaries against a specific version of Python. We
will use the default Python binary for that, which is installed in
/Library/Frameworks/Python.framework/
The Macports version is also linked against an explicit version of Python, in this case provided by Macports.
The Python package janus_swi
may be compiled against any
version of Python selected by pip. See section
7 for details.
We aim to provide an interface that is close enough to allow developing Prolog code that uses Python and visa versa. Differences between the two Prolog implementation make this non-trivial. SWI-Prolog has native support for dicts, strings, unbounded integers and blobs that provide safe pointers to external objects that are subject to (atom) garbage collection.
We try to find a compromise to make the data conversion as close as
possible while supporting both systems as good as possible. For this
reason we support creating a Python dict both from a SWI-Prolog dict and
from the Prolog term py({k1:v1, k2:v2, ...})
. With
py
defined as a prefix operator, this may be written
without parenthesis and is thus equivalent to the SWI-Prolog dict
syntax. The library(janus)
library provides access
predicates that are supported by both systems and where the SWI-Prolog
version supports both SWI-Prolog dicts and the above Prolog
representation. See
items/2, values/3, key/2
and items/2.
Both implementations will provide a low-level and more high level interface. The high level interface is realized by py_call/[2,3] and py_iter/[2,3] from Prolog and janus.once() and janus.Query() from Python. We realize the low level interfaces py_func/[3,4] and py_dot/[4,5] on top of py_call/2 and the Python functions px_cmd(), px_qdet() and px_comp() on top of janus.once(). Emulation of the Prolog predicates is shallow and has little impact on performance. Emulation of the Python functions on top of janus.once() is more expensive. Future versions of the SWI-Prolog implementation may opt for a more low-level implementation.
We are discussing to minimize the differences. The current implementation reflects the almost complete agreement calling Python from Prolog. Discussing calling Prolog from Python is work in progress.
This section will be written after the dust has settled. Topics
The current version of this Janus library must be considered beta code.