\documentclass[11pt]{article} \usepackage{times} \usepackage{pl} \usepackage{html} \sloppy \makeindex \onefile \htmloutput{\Sdot} % Output directory \htmlmainfile{janus} % Main document file \bodycolor{white} % Page colour \begin{document} \title{SWI-Prolog Python interface} \author{Jan Wielemaker \\ SWI-Prolog Solutions b.v. \\ E-mail: \email{jan@swi-prolog.org}} \maketitle \begin{abstract} This package implements a bi-directional interface between Prolog and Python using portable low-level primitives. The aim is to make Python available to Prolog and visa versa with minimal installation effort while providing a high level bi-directional interface with good performance. 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. \end{abstract} \pagebreak \tableofcontents \vfill \vfill \newpage \section{Introduction} \label{sec:janus-intro} 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 \cite{DBLP:series/lncs-0001S23,DBLP:journals/corr/abs-2308-15893}, 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 \pllib{janus}. Using Prolog from Python is as simple as \exam{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 \jargon{latency} of about one $\mu$S. The Python interface is modeled after the recent JavaScript interface developed for the WASM (Web Assembly) version. That is \begin{itemize} \item A di-directional data conversion is defined. See \secref{janus-data}. \item A Prolog predicate \index{py_call/2}\predref{py_call}{2} to call Python functions and methods, as well as access and set object attributes. \item A non-deterministic Prolog predicate \index{py_iter/2}\predref{py_iter}{2} to enumerate a Python \jargon{iterator}. \item A Python function \cfuncref{janus.once}{} to call a Prolog predicate as \index{once/1}\predref{once}{1}, providing input to Prolog variables using a Python dict and return a Python dict with bindings for each Prolog output variable. \item A Python iterator class \cfuncref{janus.Query}{} that provides access to non-deterministic Prolog predicates. \end{itemize} \section{Data conversion} \label{sec:janus-data} 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 \verb${k1:v1, k2:v2, ...}$ to dicts. Note that \verb${k1:v1, k2:v2}$ is syntactic sugar for \verb${}(','(:(k1,v1), :(k2,v2)))$. We allow for embedding this in a \term{py}{Term} such that, with \const{py} defined as \jargon{prefix operator}, \verb$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 \verb${}$ translates to a Python string, while \verb$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 \jargon{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 \index{py_call/3}\predref{py_call}{3} and \index{py_iter/3}\predref{py_iter}{3} provide the option \term{py_string_as}{string} to obtain a string if this is desirable. \begin{center} \begin{tabular}{|l|c|l|p{2in}|} \hline \textbf{Prolog} & & \textbf{Python} & \textbf{Notes} \\ \hline Variable& $\longrightarrow$ & - & (instantiation error) \\ Integer & $\Longleftrightarrow$ & int & Supports big integers \\ Rational& $\Longleftrightarrow$ & fractions.Fraction() & \\ Float & $\Longleftrightarrow$ & float & \\ @(none) & $\Longleftrightarrow$ & None & \\ @(true) & $\Longleftrightarrow$ & True & \\ @(false) & $\Longleftrightarrow$ & False & \\ Atom & $\longleftarrow$ & \cfuncref{enum.Enum}{} & Name of Enum instance \\ Atom & $\longleftrightarrow$ & String & Except the above reserved three atoms \\ String & $\longrightarrow$ & String & \\ \#(Term) & $\longrightarrow$ & String & \jargon{stringify} using \index{write_canonical/1}\predref{write_canonical}{1} if not atomic \\ prolog(Term) & $\longrightarrow$ & \cfuncref{janus.Term}{} & Represent any Prolog term \\ Term & $\longleftarrow$ & \cfuncref{janus.Term}{} & \\ List & $\longrightarrow$ & List & \\ List & $\longleftarrow$ & Sequence & \\ List & $\longleftarrow$ & Iterator & Note that a \jargon{Generator} is an \jargon{Iterator} \\ py_set(List) & $\Longleftrightarrow$ & Set & \\ -(a,b,\ldots) & $\Longleftrightarrow$ & (a,b,\ldots) & Python Tuples \\ Dict & $\Longleftrightarrow$ & Dict & \\ \{k:v,\ldots\} & $\Longrightarrow$ & Dict & Compatibility (see above) \\ py(\{k:v,\ldots\}) & $\Longrightarrow$ & Dict & Compatibility (see above) \\ eval(Term) & $\Longrightarrow$ & Object & Evaluate Term as first argument of \index{py_call/2}\predref{py_call}{2} \\ \const{py_obj} blob & $\Longleftrightarrow$ & Object & Used for any Python object not above \\ Compound & $\longrightarrow$ & - & for any term not above (type error) \\ \hline \end{tabular} \end{center} 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 \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 \cfuncref(__str__)() method of the instance returning +/-\bnfmeta{num}/\bnfmeta{den} where \bnfmeta{num} and \bnfmeta{den} are decimal numbers. The conversion \#(Term) allows passing anything as a Python string. If \arg{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 \index{write_canonical/1}\predref{write_canonical}{1}. The conversion \term{prolog}{Term} creates an instance of \cfuncref{janus.Term}{}. This class encapsulates a copy of an arbitrary Prolog term. The SWI-Prolog implementation uses the \cfuncref{PL_record}{} and \cfuncref{PL_recorded}{} functions to store and retrieve the term. Internally, \cfuncref{janus.Term}{} is used to represent Prolog exeptions that are raised during the execution of \cfuncref{janus.once}{} or \cfuncref{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., \term{f}{} and many systems have a limit on the \jargon{arity} of compound terms. Using Prolog \jargon{comma lists}, e.g., \verb$(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 \const{\Sminus} as functor to make the common binary tuple map to a Prolog \jargon{pair}. \section{Janus by example} \label{sec:janus-examples} This section introduces Janus calling Python from Prolog by examples. \subsection{Janus calling spaCy} \label{sec:janus-spacy} The \href{https://spacy.io/}{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 \begin{code} > pip install spacy > python -m spacy download en \end{code} \noindent After spaCy is installed, we can define \nopredref{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. \begin{code} :- table english/1 as shared. english(NLP) :- py_call(spacy:load(en_core_web_sm), NLP). \end{code} \noindent Calling \term{english}{X} results in \arg{X} = \verb$(0x7f703c24f430)$. This object implements the Python \jargon{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 \const{__call__} method: \begin{code} ?- english(NLP), py_call(NLP:'__call__'("This is a sentence."), Doc). NLP = (0x7f703851b8e0), Doc = [(0x7f70375be9d0), (0x7f70375be930), (0x7f70387f8860), (0x7f70376dde40), (0x7f70376de200) ]. \end{code} \noindent This is not what we want. Because the spaCy \const{Doc} class implements the \jargon{sequence} protocol it is translated into a Prolog list of spaCy \const{Token} instances. The \const{Doc} class implements many more methods that we may wish to use. An example is \const{noun_chunks}, which provides a Python \jargon{generator} that enumerates the noun chunks found in the input. Each chunk is an instance of \const{Span}, a sequence of \const{Token} instances that have the property \const{text}. So, if we want the noun chunks as text, we can write the following program: \begin{code} :- 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). \end{code} \noindent After which we can call \begin{code} ?- noun("This is a sentence.", Noun). Noun = 'This' ; Noun = 'a sentence'. \end{code} \noindent \input{libjanus.tex} \subsection{Handling Python errors in Prolog} \label{sec:janus-python-errors} If \index{py_call/2}\predref{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 \index{print_message/2}\predref{print_message}{2} to render these errors in a human readable way. \begin{quote} \term{error}{\term{python_error}{ErrorType, Value, Stack}, _} \end{quote} Here, \arg{ErrorType} is the name of the error type, as an atom, e.g., \const{'TypeError'}. \arg{Value} is the exception object represented by a Python object reference. \arg{Stack} is either \const{@none} or an object that captures the Python stack. The \pllib{janus} defines the message formatting, which makes us end up with a message like below. \begin{code} ?- py_call(nomodule:noattr). ERROR: Python 'ModuleNotFoundError': ERROR: No module named 'nomodule' ERROR: In: ERROR: [10] janus:py_call(nomodule:noattr) \end{code} \noindent \section{Calling Prolog from Python} \label{sec:janus-call-prolog} The binding can also call Prolog from Python. This can both be used to realize \jargon{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 \const{janus-swi}, which defines the module \const{janus_swi}. We do not call this simply \const{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. \begin{code} import janus_swi as janus \end{code} \noindent If Python is embedded into SWI-Prolog, the Python module may be imported both as \const{janus} and \const{janus_swi}. Using \const{janus} allows the same Python code to be used from different Prolog systems, while using \const{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 \const{janus}. The Python module \const{janus} provides utility functions and defines the classes \cfuncref{janus.Query}{}, \cfuncref{janus.Term}{} and \cfuncref{janus.PrologError}{}. We start our discussion by introducing the \cfuncref{janus.once}{query,inputs} function for calling Prolog goals as \index{once/1}\predref{once}{1}. A Prolog goal is constructed from a string and a dict with \jargon{input bindings} and returns \jargon{output bindings} as a dict. For example \begin{code} >>> import janus_swi as janus >>> janus.once("Y is X+1", {"X":1}) {'Y': 2, 'status': True} \end{code} \noindent Note that the input argument may also be passed literally. Below we give two examples. We \textbf{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 \jargon{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. \begin{code} >>> 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 \end{code} \noindent The \jargon{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 \index{parent/2}\predref{parent}{2} relations we can use the code below, where the \arg{_GP} and \arg{_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. \begin{code} >>> janus.once("findall(_GP, parent(Me, _P), parent(_P, _GP), GPs)", {'Me':'Jan'})["GPs"] [ 'Kees', 'Jan' ] \end{code} \noindent In addition to the variable bindings the dict contains a key \const{status}\footnote{Note 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 \jargon{Well Founded Semantics}, this may also be the string \const{'Undefined'}. If evaluation of the query failed, all variable bindings are bound to the Python constant \const{None} and the \const{status} key is \const{False}. The following Python function returns \const{True} if the Prolog system supports unbounded integers and \const{False} otherwise. \begin{code} def hasBigIntegers(): janus.once("current_prolog_flag(bounded,false)")['status'] \end{code} \noindent While \cfuncref{janus.once}{} deals with semi-deterministic goals, the class \cfuncref{janus.Query}{} implements a Python \jargon{iterator} that iterates over the solutions of a Prolog goal. The iterator may be aborted using the Python \exam{break} statement. As with \cfuncref{janus.once}{}, the returned dict contains a \const{status} field. This field cannot be \const{False} though and thus is either \const{True} or the string \verb$'Undefined'$.\footnote{The representation of \jargon{Undefined} is still under discussion.} \begin{code} 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"]) \end{code} \noindent Iterators may be nested. For example, we can create a list of tuples like below. \begin{code} 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 \end{code} \noindent After this, we may run \begin{code} >>> demo.double_iter(2,3) [(1, 1), (2, 1), (1, 2), (2, 2), (1, 3), (2, 3)] \end{code} \noindent In addition to the \jargon{iterator} protocol that class \cfuncref{janus.Query}{} implements, it also implements the methods \cfuncref{janus.Query.next}{} and \cfuncref{janus.Query.close}{}. This allows for e.g. \begin{code} q = Query("between(1,3,X)") while ( s := q.next() ): print(s['X']) q.close() \end{code} \noindent But, \textbf{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. \begin{code} >>> 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() \end{code} \noindent \textbf{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. \begin{description} \cfunction{dict}{janus.once}{query, bindings=\{{}\}, keep=False} Call \arg{query} using \arg{bindings} as \index{once/1}\predref{once}{1}, returning a dict with the resulting bindings. If \arg{bindings} is omitted, no variables are bound. The \arg{keep} parameter determines whether or not Prolog discards all backtrackable changes. By default, such changes are discarded and as a result, changes to backtrackable global variables are lost. Using \const{True}, such changes are preserved. \begin{code} >>> once("b_setval(a, 1)", keep=True) {'status': 'True'} >>> once("b_getval(a, X)") {'status': 'True', 'X': 1} \end{code} \noindent If \arg{query} fails, the variables of the query are bound to the Python constant \const{None}. The \arg{bindings} object includes a key \const{status}\footnote{As this name is not a valid Prolog variable name, this cannot be ambiguous.} that has the value \const{False} (query failed, all bindings are \const{None}), \const{True} (query succeeded, variables are bound to the result converting Prolog data to Python) or \verb$'Undefined'$, a Python string that indicates the answer is undefined according to the \jargon{Well Founded Semantics}. See e.g., \index{undefined/0}\predref{undefined}{0}. For example \begin{code} >>> import janus_swi as janus >>> janus.once("undefined") {'status': 'Undefined'} \end{code} \noindent \cfunction{None}{janus.consult}{file, data=None, module='user'} Load Prolog text into the Prolog database. By default, \arg{data} is \const{None} and the text is read from \arg{file}. If \arg{data} is a string, it provides the Prolog text that is loaded and \arg{file} is used as \jargon{identifier} for source locations and error messages. The \arg{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 \arg{data} is not provided and \arg{file} is not accessible this raises a Prolog exception. Errors that occur during the compilation are printed using \index{print_message/2}\predref{print_message}{2} and can currently not be captured easily. The script below prints the train connections as a list of Python tuples. \begin{code} 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")]) \end{code} \noindent \cfunction{None}{janus.prolog}{} Start the interactive Prolog toplevel. This is the Python equivalent of \index{py_shell/0}\predref{py_shell}{0}. \end{description} \subsection{Janus class Query} \label{sec:janus-class-query} Class \cfuncref{janus.Query}{} is similar to the \cfuncref{janus.once}{} function, but it returns a Python \jargon{iterator} that allows for iterating over the answers to a non-deterministic Prolog predicate. \begin{description} \cfunction{Query}{janus.Query}{query, bindings=\{{}\}, keep=False} As \cfuncref{janus.once}{}, returning an \jargon{iterator} that provides an answer dict as \cfuncref{janus.once}{} for each answer to \arg{query}. Answers never have \const{status} \const{False}. See discussion above. \cfunction{dict{\Sbar}None}{janus.Query.next}{} Explicitly ask for the next solution of the iterator. Normally, using the \ctype{Query} as an iterator is to be preferred. See discussion above. \cfunction{None}{janus.Query.close}{} Close the query. Closing a query is obligatory. When used as an iterator, the Python destructor (\cfuncref{__del__}{}) takes care of closing the query. \end{description} \subsection{Janus class Term} \label{sec:janus-class-term} Class \cfuncref{janus.Term}{} encapsulates a Prolog term. Similarly to the Python object reference (see \index{py_is_object/1}\predref{py_is_object}{1}), the class allows Python to represent arbitrary Prolog data, typically with the intend to pass it back to Prolog. \begin{description} \cfunction{Term}{janus.Term}{...} Instances are never created explicitly by the user. An instance is created by handling a term \term{prolog}{Term} tho the data conversion processes. As a result, we can do \begin{code} ?- py_call(janus:echo(prolog(hello(world))), Obj, [py_object(true)]). Obj = (0x7f7a14512050). ?- py_call(print($Obj)). hello(world) Obj = (0x7f7a14512050). \end{code} \noindent \cfunction{Term}{janus.Term.__str__}{} Return the output of \index{print/1}\predref{print}{1} on the term. This is what is used by the Python function print(). \cfunction{Term}{janus.Term.__repr__}{} Return the output of \index{write_canonical/1}\predref{write_canonical}{1} on the term. \end{description} \subsection{Janus class PrologError} \label{sec:janus-class-prolog-error} Class \cfuncref{janus.PrologError}{}, derived from the Python class \class{Exception} represents a Prolog exception that typically results from calling \cfuncref{janus.once}{} or using \cfuncref{janus.Query}{}. The class either encapsulates a string on a Prolog exception term using \class{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: \begin{code} >>> x = janus.once("X is 3.14/0")['X'] Traceback (most recent call last): ... janus.PrologError: //2: Arithmetic: evaluation error: `zero_divisor' \end{code} \noindent 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 \class{janus.PrologError} or provide a method to classify the error more easily. \begin{description} \cfunction{PrologError}{janus.PrologError}{TermOrString} The constructor may be used explicitly, but this should be very uncommon. \cfunction{String}{janus.PrologError.__str__}{} Return a human readable message for the error using \index{message_to_string/2}\predref{message_to_string}{2} \cfunction{String}{janus.PrologError.__repr__}{} Return a formal representation of the error by means of \index{write_canonical/1}\predref{write_canonical}{1}. \end{description} \section{Janus and threads} \label{sec:janus-threads} Where SWI-Prolog support native preemptively scheduled threads that exploit multiple cores, Python has a single interpreter that can switch between native threads.\footnote{Actually, 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. \index{py_call/2}\predref{py_call}{2}. In addition, the thread that created Python releases its interpreter after every call from Prolog on Python. As a result: \begin{itemize} \item Multiple Prolog threads can make calls to Python. The access to Python is \jargon{serialized}. If a Prolog thread does not want other threads to use Python it can use \index{py_with_gil/1}\predref{py_with_gil}{1}. When multiple Prolog threads make many calls to Python performance tends to drop significantly. \item Multiple Python threads can make calls to Prolog. As Python uses only one core at the same time, Prolog working on behalve of Python \jargon{synchronously} only uses one core. Prolog threads not related to Python can proceed on other cores. \item Python threading is \jargon{cooperative}. At the moment, a thread Python thread running Prolog will not allow other Python threads to make progress. Possibly that can be improved in the future. \item It appears to be possible to initialize Python in a thread. Python remains accessible from other threads after the initializing thread has terminated. \end{itemize} \section{Janus as a Python package} \label{sec:janus-python-package} The \href{https://github.com/SWI-Prolog/packages-swipy}{Janus GIT repo} provides \file{setup.py}. Janus may be installed as a Python package after downloading using \begin{code} pip install . \end{code} \noindent \program{pip} allows for installation from the git repository in a one-liner as below. \begin{code} pip install git+https://github.com/SWI-Prolog/packages-swipy.git#egg=janus_swi \end{code} \noindent Installing janus as a Python package requires \begin{itemize} \item The \program{swipl} program in the default search path. The \file{setup.py} runs \exam{swipl --dump-runtime-variables} to obtain the installation locations of the various Prolog components. On Windows, if \program{swipl} is not on \verb$%PATH%$, \file{setup.py} tries the registry to find the default binary installation. \item A C compiler that can be used by \program{pip}. The janus interface has been tested to compile using GCC, Clang and Microsoft Visual C++. \end{itemize} After successful installation we should be able to use Prolog directly from Python. For example: \begin{code} 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. ... ?- \end{code} \noindent \section{Prolog and Python} \label{sec:janus-prolog-python} Prolog is a very different language than imperative languages. An interesting similarity is the notion of \jargon{backtracking} vs. Python \jargon{iterators}. \section{Janus performance evaluation} \label{sec:janus-performance} 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. \begin{center} \begin{tabular}{|p{3in}|c|} \hline \textbf{Action} & \textbf{Time (seconds)} \\ \hline Echo list with 1,000,000 elements & 0.12 \\ Call Pyton \exam{demo:int()} from Prolog 1,000,000 times & 0.44 \\ Call Pyton \exam{demo:sumlist3(5,[1,2,3])} from Prolog 1,000,000 times & 1.4 \\ Call Prolog \exam{Y is X+1} from Python 1,000,000 times & 1.9 \\ Iterate from Python over Prolog goal \exam{between(1, 1 000 000, X)} & 1.1 \\ Iterate over Python iterator \exam{range(1,1000000)} from Prolog & 0.17 \\ \hline \end{tabular} \end{center} \section{Python or C/C++ for accessing resources?} \label{sec:janus-vs-c} 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 \jargon{GIL}, a global lock that allows for only a single thread to use Python at the same time.\footnote{There 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 \ctype{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.\footnote{Using a Python C++ interface such as \href{https://github.com/pybind/pybind11}{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. \section{Janus platforms notes} \label{sec:janus-platforms} 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. \subsection{Janus on Windows} \label{sec:janus-on-windows} We tested the Windows platform using SWI-Prolog binaries from \href{https://www.swi-prolog.org/Downloads.html}{https://www.swi-prolog.org/Downloads.html} and Python downloaded from \href{https://www.python.org/downloads/windows/}{https://www.python.org/downloads/windows/}. The SWI-Prolog binary provides \file{janus.dll} which is linked to \file{python3.dll}, a ``stable API'' based wrapper that each Python~3 binary distribution provides in addition to \file{python3xx.dll}. Calling Python from Prolog is supported out of the box, provided the folder holding \file{python3.dll} is in the search \verb$%PATH%$. The Python package can be installed using \program{pip} as described in \secref{janus-python-package}. Once built, this package finds SWI-Prolog on \verb$%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. \subsection{Janus on Linux} \label{sec:janus-on-linux} On Linux systems we bind to the currently installed Prolog and Python version. This should work smoothly from source. Janus is included in the \href{https://www.swi-prolog.org/build/PPA.html}{PPA distribution} for Ubuntu as well as in the \href{https://www.swi-prolog.org/Docker.html}{Docker images}. It is currently not part of the SNAP distribution. See \secref{janus-python-package} for for building the \const{janus_swi} Python package. \subsection{Janus on MacOS} \label{sec:janus-on-macos} Unfortunately MacOS versions of Python do not ship with the equivalent of \file{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 \file{/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 \const{janus_swi} may be compiled against any version of Python selected by \program{pip}. See \secref{janus-python-package} for details. \section{Compatibility to the XSB Janus implementation} \label{sec:janus-vs-xsb} 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 \jargon{dicts}, \jargon{strings}, \jargon{unbounded integers} and \jargon{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 \verb$py({k1:v1, k2:v2, ...})$. With \const{py} defined as a prefix operator, this may be written without parenthesis and is thus equivalent to the SWI-Prolog dict syntax. The \pllib{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 \index{items/2}\predref{items}{2}, \index{values/3}\predref{values}{3}, \index{key/2}\predref{key}{2} and \index{items/2}\predref{items}{2}. Both implementations will provide a low-level and more high level interface. The high level interface is realized by \index{py_call/[2,3]}\predref{py_call}{[2,3]} and \index{py_iter/[2,3]}\predref{py_iter}{[2,3]} from Prolog and janus.once() and janus.Query() from Python. We realize the low level interfaces \index{py_func/[3,4]}\predref{py_func}{[3,4]} and \index{py_dot/[4,5]}\predref{py_dot}{[4,5]} on top of \index{py_call/2}\predref{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. \subsection{Writing portable Janus modules} \label{sec:janus-portable-code} This section will be written after the dust has settled. Topics \begin{itemize} \item Dealing with Python dicts \item Dealing with Prolog modules \item Dealing with Prolog references to Python objects \item More? \end{itemize} \section{Status of Janus} \label{sec:janus-status} The current version of this Janus library must be considered \jargon{beta} code. \begin{itemize} \item The design is stable \item Prolog predicates have been agreed upon \item Testing is not exhaustive. \end{itemize} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \bibliographystyle{name} \bibliography{pl} \printindex \end{document}