View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2023-2024, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(janus,
   36          [ py_version/0,
   37
   38            py_call/1,                  % +Call
   39            py_call/2,                  % +Call, -Return
   40            py_call/3,                  % +Call, -Return, +Options
   41	    py_iter/2,			% +Call, -Return
   42	    py_iter/3,			% +Call, -Return, +Options
   43            py_setattr/3,               % +On, +Name, +Value
   44            py_free/1,			% +Obj
   45	    py_is_object/1,		% @Term
   46	    py_is_dict/1,		% @Term
   47	    py_with_gil/1,		% :Goal
   48	    py_gil_owner/1,		% -ThreadID
   49
   50            py_func/3,                  % +Module, +Func, -Return
   51            py_func/4,                  % +Module, +Func, -Return, +Options
   52            py_dot/3,                   % +ObjRef, +Meth, ?Ret
   53            py_dot/4,                   % +ObjRef, +Meth, -Ret, +Options
   54
   55            values/3,                   % +Dict, +Path, ?Val
   56            keys/2,                     % +Dict, ?Keys
   57            key/2,                      % +Dict, ?Key
   58            items/2,                    % +Dict, ?Items
   59
   60            py_shell/0,
   61
   62	    py_pp/1,                    % +Term
   63            py_pp/2,                    % +Stream, +Term
   64            py_pp/3,                    % +Stream, +Term, +Options
   65
   66            py_object_dir/2,            % +ObjRef, -List
   67            py_object_dict/2,           % +ObjRef, -Dict
   68            py_obj_dir/2,               % +ObjRef, -List (deprecated)
   69            py_obj_dict/2,              % +ObjRef, -Dict (deprecated)
   70            py_type/2,			% +ObjRef, -Type:atom
   71            py_isinstance/2,            % +ObjRef, +Type
   72            py_module_exists/1,         % +Module
   73            py_hasattr/2,               % +Module, ?Symbol
   74
   75            py_import/2,                % +Spec, +Options
   76            py_module/2,                % +Module:atom, +Source:string
   77
   78            py_initialize/3,            % +Program, +Argv, +Options
   79            py_lib_dirs/1,              % -Dirs
   80            py_add_lib_dir/1,           % +Dir
   81            py_add_lib_dir/2,           % +Dir,+Where
   82
   83            op(200, fy, @),             % @constant
   84            op(50,  fx, #)              % #Value
   85          ]).   86:- meta_predicate py_with_gil(0).   87
   88:- use_module(library(apply_macros), []).   89:- autoload(library(lists), [append/3, member/2, append/2, last/2]).   90:- autoload(library(apply),
   91            [maplist/2, exclude/3, maplist/3, convlist/3, partition/4]).   92:- autoload(library(error), [must_be/2, domain_error/2]).   93:- autoload(library(dicts), [dict_keys/2]).   94:- autoload(library(option), [dict_options/2, select_option/4, option/2]).   95:- autoload(library(prolog_code), [comma_list/2]).   96:- autoload(library(readutil), [read_line_to_string/2, read_file_to_string/3]).   97:- autoload(library(wfs), [call_delays/2, delays_residual_program/2]).   98:- autoload(library(dcg/high_order), [sequence//2, sequence//3]).   99
  100:- if(\+current_predicate(py_call/1)).  101:- if(current_prolog_flag(windows, true)).  102:- use_module(library(shlib), [win_add_dll_directory/1]).  103
  104% Just having the Python dir in PATH seems insufficient. We also need to
  105% add the directory to the DLL search path.
  106add_python_dll_dir :-
  107    (   current_prolog_flag(msys2, true)
  108    ->  absolute_file_name(path('libpython3.dll'), DLL, [access(read)])
  109    ;   absolute_file_name(path('python3.dll'), DLL, [access(read)])
  110    ),
  111    file_directory_name(DLL, Dir),
  112    win_add_dll_directory(Dir).
  113:- initialization(add_python_dll_dir, now).  114:- endif.  115
  116:- use_foreign_library(foreign(janus), [visibility(global)]).  117:- endif.  118
  119:- predicate_options(py_call/3, 3,
  120                     [ py_object(boolean),
  121                       py_string_as(oneof([string,atom]))
  122                     ]).  123:- predicate_options(py_func/4, 4,
  124                     [ pass_to(py_call/3, 3)
  125                     ]).  126:- predicate_options(py_dot/5, 5,
  127                     [ pass_to(py_call/3, 3)
  128                     ]).  129
  130:- public
  131    py_initialize/0,
  132    py_call_string/3,
  133    py_write/2,
  134    py_readline/4.  135
  136:- create_prolog_flag(py_backtrace,       true, [type(boolean), keep(true)]).  137:- create_prolog_flag(py_backtrace_depth, 4,    [type(integer), keep(true)]).  138:- create_prolog_flag(py_argv,		  [],   [type(term), keep(true)]).

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

 py_version is det
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.
  160py_version :-
  161    py_call(sys:version, PythonVersion),
  162    py_call(janus_swi:version_str(), JanusVersion),
  163    print_message(information, janus(version(JanusVersion, PythonVersion))),
  164    (   py_venv(VEnvDir, EnvSiteDir)
  165    ->  print_message(information, janus(venv(VEnvDir, EnvSiteDir)))
  166    ;   true
  167    ).
 py_call(+Call) is det
 py_call(+Call, -Return) is det
 py_call(+Call, -Return, +Options) is det
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.
 py_iter(+Iterator, -Value) is nondet
 py_iter(+Iterator, -Value, +Options) is nondet
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
Arguments:
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.
 py_setattr(+Target, +Name, +Value) is det
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
 py_run(+String, +Globals, +Locals, -Result, +Options) is det
Interface to Py_CompileString() followed by PyEval_EvalCode(). Options:
file_name(String)
Errors are reported against this pseudo file name
start(Token)
One of eval, file (default) or single.
Arguments:
Globals- is a dict
Locals- is a dict
 py_is_object(@Term) is semidet
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.
 py_is_dict(@Term) is semidet
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.
  364py_is_dict(Dict), is_dict(Dict) => true.
  365py_is_dict(py({})) => true.
  366py_is_dict(py({KV})) => is_kv(KV).
  367py_is_dict({KV}) => is_kv(KV).
  368
  369is_kv((K:V,T)) => ground(K), ground(V), is_kv(T).
  370is_kv(K:V) => ground(K), ground(V).
 py_free(+Obj) is det
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.
 py_with_gil(:Goal) is semidet
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.
 py_gil_owner(-Thread) is semidet
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.

  414		 /*******************************
  415		 *         COMPATIBILIY		*
  416		 *******************************/
 py_func(+Module, +Function, -Return) is det
 py_func(+Module, +Function, -Return, +Options) is det
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.
  430py_func(Module, Function, Return) :-
  431    py_call(Module:Function, Return).
  432py_func(Module, Function, Return, Options) :-
  433    py_call(Module:Function, Return, Options).
 py_dot(+ObjRef, +MethAttr, -Ret) is det
 py_dot(+ObjRef, +MethAttr, -Ret, +Options) is det
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.
  444py_dot(ObjRef, MethAttr, Ret) :-
  445    py_call(ObjRef:MethAttr, Ret).
  446py_dot(ObjRef, MethAttr, Ret, Options) :-
  447    py_call(ObjRef:MethAttr, Ret, Options).
  448
  449
  450		 /*******************************
  451		 *   PORTABLE ACCESS TO DICTS	*
  452		 *******************************/
 values(+Dict, +Path, ?Val) is semidet
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, ...}.
  462values(Dict, Key, Val), is_dict(Dict), atom(Key) =>
  463    get_dict(Key, Dict, Val).
  464values(Dict, Keys, Val), is_dict(Dict), is_list(Keys) =>
  465    get_dict_path(Keys, Dict, Val).
  466values(py({CommaDict}), Key, Val) =>
  467    comma_values(CommaDict, Key, Val).
  468values({CommaDict}, Key, Val) =>
  469    comma_values(CommaDict, Key, Val).
  470
  471get_dict_path([], Val, Val).
  472get_dict_path([H|T], Dict, Val) :-
  473    get_dict(H, Dict, Val0),
  474    get_dict_path(T, Val0, Val).
  475
  476comma_values(CommaDict, Key, Val), atom(Key) =>
  477    comma_value(Key, CommaDict, Val).
  478comma_values(CommaDict, Keys, Val), is_list(Keys) =>
  479    comma_value_path(Keys, CommaDict, Val).
  480
  481comma_value(Key, Key:Val0, Val) =>
  482    Val = Val0.
  483comma_value(Key, (_,Tail), Val) =>
  484    comma_value(Key, Tail, Val).
  485
  486comma_value_path([], Val, Val).
  487comma_value_path([H|T], Dict, Val) :-
  488    comma_value(H, Dict, Val0),
  489    comma_value_path(T, Val0, Val).
 keys(+Dict, ?Keys) is det
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, ...}.
  498keys(Dict, Keys), is_dict(Dict) =>
  499    dict_keys(Dict, Keys).
  500keys(py({CommaDict}), Keys) =>
  501    comma_dict_keys(CommaDict, Keys).
  502keys({CommaDict}, Keys) =>
  503    comma_dict_keys(CommaDict, Keys).
  504
  505comma_dict_keys((Key:_,T), Keys) =>
  506    Keys = [Key|KT],
  507    comma_dict_keys(T, KT).
  508comma_dict_keys(Key:_, Keys) =>
  509    Keys = [Key].
 key(+Dict, ?Key) is nondet
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, ...}.
  519key(Dict, Key), is_dict(Dict) =>
  520    dict_pairs(Dict, _Tag, Pairs),
  521    member(Key-_, Pairs).
  522key(py({CommaDict}), Keys) =>
  523    comma_dict_key(CommaDict, Keys).
  524key({CommaDict}, Keys) =>
  525    comma_dict_key(CommaDict, Keys).
  526
  527comma_dict_key((Key:_,_), Key).
  528comma_dict_key((_,T), Key) :-
  529    comma_dict_key(T, Key).
 items(+Dict, ?Items) is det
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, ...}.
  538items(Dict, Items), is_dict(Dict) =>
  539    dict_pairs(Dict, _, Pairs),
  540    maplist(pair_item, Pairs, Items).
  541items(py({CommaDict}), Keys) =>
  542    comma_dict_items(CommaDict, Keys).
  543items({CommaDict}, Keys) =>
  544    comma_dict_items(CommaDict, Keys).
  545
  546pair_item(K-V, K:V).
  547
  548comma_dict_items((Key:Value,T), Keys) =>
  549    Keys = [Key:Value|KT],
  550    comma_dict_items(T, KT).
  551comma_dict_items(Key:Value, Keys) =>
  552    Keys = [Key:Value].
  553
  554
  555		 /*******************************
  556		 *             SHELL		*
  557		 *******************************/
 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.

  583py_shell :-
  584    import_janus,
  585    py_call(janus_swi:interact(), _).
  586
  587import_janus :-
  588    py_call(sys:hexversion, V),
  589    V >= 0x030A0000,                    % >= 3.10
  590    !,
  591    py_run("from janus_swi import *", py{}, py{}, _, []).
  592import_janus :-
  593    print_message(warning, janus(py_shell(no_janus))).
  594
  595
  596		 /*******************************
  597		 *          UTILITIES           *
  598		 *******************************/
 py_pp(+Term) is det
 py_pp(+Term, +Options) is det
 py_pp(+Stream, +Term, +Options) is det
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
  620py_pp(Term) :-
  621    py_pp(current_output, Term, []).
  622
  623py_pp(Term, Options) :-
  624    py_pp(current_output, Term, Options).
  625
  626py_pp(Stream, Term, Options) :-
  627    select_option(nl(NL), Options, Options1, true),
  628    (   NL == true
  629    ->  Method = pp
  630    ;   Method = pformat
  631    ),
  632    opts_kws(Options1, Kws),
  633    PFormat =.. [Method, Term|Kws],
  634    py_call(pprint:PFormat, String),
  635    write(Stream, String).
  636
  637opts_kws(Options, Kws) :-
  638    dict_options(Dict, Options),
  639    dict_pairs(Dict, _, Pairs),
  640    maplist(pair_kws, Pairs, Kws).
  641
  642pair_kws(Name-Value, Name=Value).
 py_object_dir(+ObjRef, -List) is det
 py_object_dict(+ObjRef, -Dict) is det
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
  654py_object_dir(ObjRef, List) :-
  655    py_call(ObjRef:'__dir__'(), List).
  656
  657py_object_dict(ObjRef, Dict) :-
  658    py_call(ObjRef:'__dict__', Dict).
 py_obj_dir(+ObjRef, -List) is det
 py_obj_dict(+ObjRef, -Dict) is det
deprecated
- Use py_object_dir/2 or py_object_dict/2.
  665py_obj_dir(ObjRef, List) :-
  666    py_object_dir(ObjRef, List).
  667
  668py_obj_dict(ObjRef, Dict) :-
  669    py_object_dict(ObjRef, Dict).
 py_type(+ObjRef, -Type:atom) is det
True when Type is the name of the type of ObjRef. This is the same as type(ObjRef).__name__ in Python.
Compatibility
- PIP
  679py_type(ObjRef, Type) :-
  680    py_call(type(ObjRef):'__name__', Type).
 py_isinstance(+ObjRef, +Type) is semidet
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.
Arguments:
Type- is either a term Module:Type or a plain atom to refer to a built-in type.
Compatibility
- PIP
  693py_isinstance(Obj, Module:Type) =>
  694    py_call(isinstance(Obj, eval(Module:Type)), @true).
  695py_isinstance(Obj, Type) =>
  696    py_call(isinstance(Obj, eval(sys:modules:'__getitem__'(builtins):Type)), @true).
 py_module_exists(+Module) is semidet
True if Module is a currently loaded Python module or it can be loaded.
Compatibility
- PIP
  705py_module_exists(Module) :-
  706    must_be(atom, Module),
  707    py_call(sys:modules:'__contains__'(Module), @true),
  708    !.
  709py_module_exists(Module) :-
  710    py_call(importlib:util:find_spec(Module), R),
  711    R \== @none,
  712    py_free(R).
 py_hasattr(+ModuleOrObj, ?Name) is nondet
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.
Arguments:
ModuleOrObj- If this is an atom it refers to a module, otherwise it must be a Python object reference.
Compatibility
- PIP
  725py_hasattr(ModuleOrObj, Name) :-
  726    var(Name),
  727    !,
  728    py_object_dir(ModuleOrObj, Names),
  729    member(Name, Names).
  730py_hasattr(ModuleOrObj, Name) :-
  731    must_be(atom, Name),
  732    (   atom(ModuleOrObj)
  733    ->  py_call(ModuleOrObj:'__name__'), % force loading
  734        py_call(hasattr(eval(sys:modules:'__getitem__'(ModuleOrObj)), Name), @true)
  735    ;   py_call(hasattr(ModuleOrObj, Name), @true)
  736    ).
 py_import(+Spec, +Options) is det
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.
  774py_import(Spec, Options) :-
  775    option(as(_), Options),
  776    !,
  777    py_import_(Spec, Options).
  778py_import(Spec, Options) :-
  779    split_string(Spec, ".", "", Parts),
  780    last(Parts, Last),
  781    atom_string(As, Last),
  782    py_import_(Spec, [as(As)|Options]).
 py_module(+Module:atom, +Source:string) is det
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.
  805:- dynamic py_dyn_module/2 as volatile.  806
  807py_module(Module, Source) :-
  808    variant_sha1(Source, Hash),
  809    (   py_dyn_module(Module, Hash)
  810    ->  true
  811    ;   py_call(janus:import_module_from_string(Module, Source)),
  812        (   retract(py_dyn_module(Module, _))
  813        ->  py_update_module_cache(Module)
  814        ;   true
  815        ),
  816        asserta(py_dyn_module(Module, Hash))
  817    ).
  818
  819
  820		 /*******************************
  821		 *            INIT		*
  822		 *******************************/
  823
  824:- dynamic py_venv/2 as volatile.  825:- dynamic py_is_initialized/0 as volatile.  826
  827%   py_initialize is det.
  828%
  829%   Used as a callback from C for lazy initialization of Python.
  830
  831py_initialize :-
  832    getenv('VIRTUAL_ENV', VEnv),
  833    prolog_to_os_filename(VEnvDir, VEnv),
  834    atom_concat(VEnvDir, '/pyvenv.cfg', Cfg),
  835    venv_config(Cfg, Config),
  836    !,
  837    current_prolog_flag(executable, Program),
  838    current_prolog_flag(py_argv, Argv),
  839    py_initialize(Program, ['-I'|Argv], []),
  840    py_setattr(sys, prefix, VEnv),
  841    venv_update_path(VEnvDir, Config).
  842py_initialize :-
  843    current_prolog_flag(executable, Program),
  844    current_prolog_flag(py_argv, Argv),
  845    py_initialize(Program, Argv, []).
  846
  847venv_config(File, Config) :-
  848    access_file(File, read),
  849    read_file_to_string(File, String, []),
  850    split_string(String, "\n", "\n\r", Lines),
  851    convlist(venv_config_line, Lines, Config).
  852
  853venv_config_line(Line, Config) :-
  854    sub_string(Line, B, _, A, "="),
  855    !,
  856    sub_string(Line, 0, B, _, NameS),
  857    split_string(NameS, "", "\t\s", [NameS2]),
  858    atom_string(Name, NameS2),
  859    sub_string(Line, _, A, 0, ValueS),
  860    split_string(ValueS, "", "\t\s", [ValueS2]),
  861    (   number_string(Value, ValueS2)
  862    ->  true
  863    ;   atom_string(Value, ValueS2)
  864    ),
  865    Config =.. [Name,Value].
  866
  867venv_update_path(VEnvDir, Options) :-
  868    py_call(sys:version_info, Info),    % Tuple
  869    Info =.. [_,Major,Minor|_],
  870    format(string(EnvSiteDir),
  871           '~w/lib/python~w.~w/site-packages',
  872           [VEnvDir, Major, Minor]),
  873    prolog_to_os_filename(EnvSiteDir, PyEnvSiteDir),
  874    (   exists_directory(EnvSiteDir)
  875    ->  true
  876    ;   print_message(warning,
  877                      janus(venv(no_site_package_dir(VEnvDir, EnvSiteDir))))
  878    ),
  879    py_call(sys:path, Path0),
  880    (   option('include-system-site-packages'(true), Options)
  881    ->  partition(is_site_dir, Path0, PkgPath, SysPath),
  882        append([SysPath,[PyEnvSiteDir], PkgPath], Path)
  883    ;   exclude(is_site_dir, Path0, Path1),
  884        append(Path1, [PyEnvSiteDir], Path)
  885    ),
  886    py_setattr(sys, path, Path),
  887    print_message(silent, janus(venv(VEnvDir, EnvSiteDir))),
  888    asserta(py_venv(VEnvDir, EnvSiteDir)).
  889
  890is_site_dir(OsDir) :-
  891    prolog_to_os_filename(PlDir, OsDir),
  892    file_base_name(PlDir, Dir0),
  893    downcase_atom(Dir0, Dir),
  894    no_env_dir(Dir).
  895
  896no_env_dir('site-packages').
  897no_env_dir('dist-packages').
 py_initialize(+Program, +Argv, +Options) is det
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

Arguments:
Options- is currently ignored. It will be used to provide additional configuration options.
  921py_initialize(Program, Argv, Options) :-
  922    (   py_initialize_(Program, Argv, Options)
  923    ->  absolute_file_name(library('python/janus.py'), Janus,
  924			   [ access(read) ]),
  925	file_directory_name(Janus, PythonDir),
  926	py_add_lib_dir(PythonDir, first),
  927	py_connect_io,
  928        repl_add_cwd,
  929        asserta(py_is_initialized)
  930    ;   true
  931    ).
 py_connect_io is det
If SWI-Prolog console streams are bound to something non-standard, bind the Python console I/O to our streans.
  938py_connect_io :-
  939    maplist(non_file_stream,
  940	    [0-user_input, 1-user_output, 2-user_error],
  941	    NonFiles),
  942    Call =.. [connect_io|NonFiles],
  943    py_call(janus_swi:Call).
  944
  945non_file_stream(Expect-Stream, Bool) :-
  946    (   stream_property(Stream, file_no(Expect))
  947    ->  Bool = @false
  948    ;   Bool = @true
  949    ).
  950
  951		 /*******************************
  952		 *            PATHS		*
  953		 *******************************/
 py_lib_dirs(-Dirs) is det
True when Dirs is a list of directories searched for Python modules. The elements of Dirs are in Prolog canonical notation.
Compatibility
- PIP
  962py_lib_dirs(Dirs) :-
  963    py_call(sys:path, Dirs0),
  964    maplist(prolog_to_os_filename, Dirs, Dirs0).
 py_add_lib_dir(+Dir) is det
 py_add_lib_dir(+Dir, +Where) is det
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.
  986:- multifile system:term_expansion/2.  987
  988system:term_expansion((:- py_add_lib_dir(Dir0)), Directive) :-
  989    system:term_expansion((:- py_add_lib_dir(Dir0, last)), Directive).
  990system:term_expansion((:- py_add_lib_dir(Dir0, Where)),
  991                      (:- initialization(py_add_lib_dir(Dir, Where), now))) :-
  992    \+ (atomic(Dir0), is_absolute_file_name(Dir0)),
  993    prolog_load_context(directory, CWD),
  994    absolute_file_name(Dir0, Dir,
  995                       [ relative_to(CWD),
  996                         file_type(directory),
  997                         access(read)
  998                       ]).
  999
 1000py_add_lib_dir(Dir) :-
 1001    py_add_lib_dir(Dir, last).
 1002
 1003py_add_lib_dir(Dir, Where) :-
 1004    atomic(Dir),
 1005    !,
 1006    absolute_file_name(Dir, AbsDir),
 1007    prolog_to_os_filename(AbsDir, OSDir),
 1008    py_add_lib_dir_(OSDir, Where).
 1009py_add_lib_dir(Alias, Where) :-
 1010    absolute_file_name(Alias, AbsDir,
 1011                       [ file_type(directory),
 1012                         access(read)
 1013                       ]),
 1014    prolog_to_os_filename(AbsDir, OSDir),
 1015    py_add_lib_dir_(OSDir, Where).
 1016
 1017py_add_lib_dir_(OSDir, Where) :-
 1018    (   py_call(sys:path, Dirs0),
 1019        memberchk(OSDir, Dirs0)
 1020    ->  true
 1021    ;   Where == last
 1022    ->  py_call(sys:path:append(OSDir), _)
 1023    ;   Where == first
 1024    ->  py_call(sys:path:insert(0, OSDir), _)
 1025    ;   must_be(oneof([first,last]), Where)
 1026    ).
 1027
 1028:- det(repl_add_cwd/0). 1029repl_add_cwd :-
 1030    current_prolog_flag(break_level, Level),
 1031    Level >= 0,
 1032    !,
 1033    (   py_call(sys:path:count(''), N),
 1034        N > 0
 1035    ->  true
 1036    ;   print_message(informational, janus(add_cwd)),
 1037        py_add_lib_dir_('', first)
 1038    ).
 1039repl_add_cwd.
 1040
 1041:- multifile
 1042    prolog:repl_loop_hook/2. 1043
 1044prolog:repl_loop_hook(begin, Level) :-
 1045    Level >= 0,
 1046    py_is_initialized,
 1047    repl_add_cwd.
 1048
 1049
 1050		 /*******************************
 1051		 *           CALLBACK		*
 1052		 *******************************/
 1053
 1054:- dynamic py_call_cache/8 as volatile. 1055
 1056:- meta_predicate py_call_string(:, +, -). 1057
 1058%   py_call_string(:String, +DictIn, -Dict) is nondet.
 1059%
 1060%   Support janus.query_once() and janus.query(). Parses   String  into a goal
 1061%   term. Next, all variables from the goal   term that appear in DictIn
 1062%   are bound to the value from  this   dict.  Dict  is created from the
 1063%   remaining variables, unless they  start   with  an underscore (e.g.,
 1064%   `_Time`) and the key `truth. On   success,  the Dict values contain
 1065%   the bindings from the  answer  and   `truth`  is  either  `true` or
 1066%   `Undefined`. On failure, the Dict values are bound to `None` and the
 1067%   `truth` is `false`.
 1068%
 1069%   Parsing and distributing the variables over the two dicts is cached.
 1070
 1071py_call_string(M:String, Input, Dict) :-
 1072    py_call_cache(String, Input, TV, M, Goal, Dict, Truth, OutVars),
 1073    !,
 1074    py_call(TV, M:Goal, Truth, OutVars).
 1075py_call_string(M:String, Input, Dict) :-
 1076    term_string(Goal, String, [variable_names(Map)]),
 1077    unbind_dict(Input, VInput),
 1078    exclude(not_in_projection(VInput), Map, OutBindings),
 1079    dict_create(Dict, bindings, [truth=Truth|OutBindings]),
 1080    maplist(arg(2), OutBindings, OutVars),
 1081    TV = Input.get(truth, 'PLAIN_TRUTHVALS'),
 1082    asserta(py_call_cache(String, VInput, TV, M, Goal, Dict, Truth, OutVars)),
 1083    VInput = Input,
 1084    py_call(TV, M:Goal, Truth, OutVars).
 1085
 1086py_call('NO_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1087    (   call(M:Goal)
 1088    *-> bind_status_no_no_truthvals(Truth)
 1089    ;   Truth = @false,
 1090	maplist(bind_none, OutVars)
 1091    ).
 1092py_call('PLAIN_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1093    (   call(M:Goal)
 1094    *-> bind_status_plain_truthvals(Truth)
 1095    ;   Truth = @false,
 1096	maplist(bind_none, OutVars)
 1097    ).
 1098py_call('DELAY_LISTS', M:Goal, Truth, OutVars) =>
 1099    (   call_delays(M:Goal, Delays)
 1100    *-> bind_status_delay_lists(Delays, Truth)
 1101    ;   Truth = @false,
 1102	maplist(bind_none, OutVars)
 1103    ).
 1104py_call('RESIDUAL_PROGRAM', M:Goal, Truth, OutVars) =>
 1105    (   call_delays(M:Goal, Delays)
 1106    *-> bind_status_residual_program(Delays, Truth)
 1107    ;   Truth = @false,
 1108	maplist(bind_none, OutVars)
 1109    ).
 1110
 1111not_in_projection(Input, Name=Value) :-
 1112    (   get_dict(Name, Input, Value)
 1113    ->  true
 1114    ;   sub_atom(Name, 0, _, _, '_')
 1115    ).
 1116
 1117bind_none(@none).
 1118
 1119bind_status_no_no_truthvals(@true).
 1120
 1121bind_status_plain_truthvals(Truth) =>
 1122    (   '$tbl_delay_list'([])
 1123    ->  Truth = @true
 1124    ;   py_undefined(Truth)
 1125    ).
 1126
 1127bind_status_delay_lists(true, Truth) =>
 1128    Truth = @true.
 1129bind_status_delay_lists(Delays, Truth) =>
 1130    py_call(janus:'Undefined'(prolog(Delays)), Truth).
 1131
 1132bind_status_residual_program(true, Truth) =>
 1133    Truth = @true.
 1134bind_status_residual_program(Delays, Truth) =>
 1135    delays_residual_program(Delays, Program),
 1136    py_call(janus:'Undefined'(prolog(Program)), Truth).
 1137
 1138py_undefined(X) :-
 1139    py_call(janus:undefined, X).
 1140
 1141unbind_dict(Dict0, Dict) :-
 1142    dict_pairs(Dict0, Tag, Pairs0),
 1143    maplist(unbind, Pairs0, Pairs),
 1144    dict_pairs(Dict, Tag, Pairs).
 1145
 1146unbind(Name-_, Name-_) :-
 1147    sub_atom(Name, 0, 1, _, Char1),
 1148    char_type(Char1, prolog_var_start),
 1149    !.
 1150unbind(NonVar, NonVar).
 1151
 1152
 1153		 /*******************************
 1154		 *     SUPPORT PYTHON CALLS     *
 1155		 *******************************/
 1156
 1157:- public
 1158       px_cmd/3,
 1159       px_call/4,
 1160       px_comp/7. 1161
 1162% These predicates are helpers  for the corresponding Python functions
 1163% in janus.py.
 1164
 1165
 1166%   px_call(+Input:tuple, +Module, -Pred, -Ret)
 1167%
 1168%   Supports  px_qdet()  and  apply().  Note    that   these  predicates
 1169%   explicitly address predicates  in  a   particular  module.  For meta
 1170%   predicates, this implies they also control  the context module. This
 1171%   leads to ``janus.cmd("consult", "consult", file)`` to consult _file_
 1172%   into the module `consult`, which is not   what we want. Therefore we
 1173%   set the context module to `user`, which is better, but probably also
 1174%   not what we want.
 1175
 1176px_call(-(), Module, Pred, Ret) =>
 1177    @(call(Module:Pred, Ret), user).
 1178px_call(-(A1), Module, Pred, Ret) =>
 1179    @(call(Module:Pred, A1, Ret), user).
 1180px_call(-(A1,A2), Module, Pred, Ret) =>
 1181    @(call(Module:Pred, A1, A2, Ret), user).
 1182px_call(-(A1,A2,A3), Module, Pred, Ret) =>
 1183    @(call(Module:Pred, A1, A2, A3, Ret), user).
 1184px_call(-(A1,A2,A3,A4), Module, Pred, Ret) =>
 1185    @(call(Module:Pred, A1, A2, A3, A4, Ret), user).
 1186px_call(Tuple, Module, Pred, Ret) =>
 1187    compound_name_arguments(Tuple, _, Args),
 1188    append(Args, [Ret], GArgs),
 1189    Goal =.. [Pred|GArgs],
 1190    @(Module:Goal, user).
 1191
 1192px_cmd(Module, Pred, Tuple) :-
 1193    (   compound(Tuple)
 1194    ->  compound_name_arguments(Tuple, _, Args),
 1195	Goal =.. [Pred|Args]
 1196    ;   Goal = Pred
 1197    ),
 1198    @(Module:Goal, user).
 1199
 1200px_comp(Module, Pred, Tuple, Vars, Set, TV, Ret) :-
 1201    length(Out, Vars),
 1202    (   compound(Tuple)
 1203    ->  compound_name_arguments(Tuple, _, Args),
 1204	append(Args, Out, GArgs),
 1205	Goal =.. [Pred|GArgs]
 1206    ;   Goal =.. [Pred|Out]
 1207    ),
 1208    compound_name_arguments(OTempl0, -, Out),
 1209    tv_goal_and_template(TV, @(Module:Goal, user), FGoal, OTempl0, OTempl),
 1210    findall(OTempl, FGoal, Ret0),
 1211    (   Set == @true
 1212    ->  sort(Ret0, Ret)
 1213    ;   Ret = Ret0
 1214    ).
 1215
 1216:- meta_predicate
 1217    call_delays_py(0, -). 1218
 1219% 0,1,2: TruthVal(Enum) from janus.py
 1220tv_goal_and_template('NO_TRUTHVALS',
 1221                     Goal, Goal, Templ, Templ) :- !.
 1222tv_goal_and_template('PLAIN_TRUTHVALS',
 1223                     Goal, ucall(Goal, TV), Templ, -(Templ,TV)) :- !.
 1224tv_goal_and_template('DELAY_LISTS',
 1225                     Goal, call_delays_py(Goal, TV), Templ, -(Templ,TV)) :- !.
 1226tv_goal_and_template(Mode, _, _, _, _) :-
 1227    domain_error("px_comp() truth", Mode).
 1228
 1229:- public
 1230    ucall/2,
 1231    call_delays_py/2. 1232
 1233ucall(Goal, TV) :-
 1234    call(Goal),
 1235    (   '$tbl_delay_list'([])
 1236    ->  TV = 1
 1237    ;   TV = 2
 1238    ).
 1239
 1240call_delays_py(Goal, PyDelays) :-
 1241    call_delays(Goal, Delays),
 1242    (   Delays == true
 1243    ->  PyDelays = []
 1244    ;   comma_list(Delays, Array),
 1245        maplist(term_string, Array, PyDelays)
 1246    ).
 1247
 1248
 1249		 /*******************************
 1250		 *          PYTHON I/O          *
 1251		 *******************************/
 1252
 1253%   py_write(+Stream, -String) is det.
 1254%   py_readline(+Stream, +Size, +Prompt, +Line) is det.
 1255%
 1256%   Called from redefined Python console  I/O   to  write/read using the
 1257%   Prolog streams.
 1258
 1259:- '$hide'((py_write/1,
 1260	    py_readline/4)). 1261
 1262py_write(Stream, String) :-
 1263    notrace(format(Stream, '~s', [String])).
 1264
 1265py_readline(Stream, Size, Prompt, Line) :-
 1266    notrace(py_readline_(Stream, Size, Prompt, Line)).
 1267
 1268py_readline_(Stream, _Size, Prompt, Line) :-
 1269    prompt1(Prompt),
 1270    read_line_to_string(Stream, Read),
 1271    (   Read == end_of_file
 1272    ->  Line = ""
 1273    ;   string_concat(Read, "\n", Line),
 1274	py_add_history(Read)
 1275    ).
 1276
 1277py_add_history(Line) :-
 1278    ignore(catch(prolog:history(user_input, add(Line)), _, true)).
 1279
 1280
 1281		 /*******************************
 1282		 *          COMPILING           *
 1283		 *******************************/
 1284
 1285%   py_consult(+File, +Data, +Module) is det.
 1286%
 1287%   Support janus.consult(file, data=None, module='user').
 1288
 1289:- public py_consult/3. 1290py_consult(File, @none, Module) =>
 1291    consult(Module:File).
 1292py_consult(File, Data, Module) =>
 1293    setup_call_cleanup(
 1294	open_string(Data, In),
 1295	load_files(Module:File, [stream(In)]),
 1296	close(In)).
 1297
 1298
 1299		 /*******************************
 1300		 *           MESSAGES		*
 1301		 *******************************/
 1302
 1303:- multifile
 1304    prolog:error_message//1,
 1305    prolog:message_context//1,
 1306    prolog:message//1. 1307
 1308prolog:error_message(python_error(Class, Value)) -->
 1309    { py_str(Value, Message)
 1310    },
 1311    [ 'Python ', ansi(code, "'~w'", [Class]), ':', nl,
 1312      '  ~w'-[Message]
 1313    ].
 1314prolog:error_message(permission_error(import_as, py_module, As)) -->
 1315    [ 'Janus: No permission to import a module as ', ansi(code, '~q', As),
 1316      ': module exists.'
 1317    ].
 1318
 1319prolog:message_context(context(_, PythonCtx)) -->
 1320    { nonvar(PythonCtx),
 1321      PythonCtx = python_stack(Stack),
 1322      current_prolog_flag(py_backtrace, true),
 1323      py_is_object(Stack),
 1324      !,
 1325      current_prolog_flag(py_backtrace_depth, Depth),
 1326      py_call(traceback:format_tb(Stack, Depth), Frames)
 1327    },
 1328    [ nl, 'Python stack:', nl ],
 1329    sequence(py_stack_frame, Frames).
 1330
 1331py_stack_frame(String) -->
 1332    { split_string(String, "\n", "", Lines)
 1333    },
 1334    sequence(msg_line, [nl], Lines).
 1335
 1336msg_line(Line) -->
 1337    [ '~s'-[Line] ].
 1338
 1339prolog:message(janus(Msg)) -->
 1340    message(Msg).
 1341
 1342message(version(Janus, Python)) -->
 1343    [ 'Janus ~w embeds Python ~w'-[Janus, Python] ].
 1344message(venv(Dir, _EnvSiteDir)) -->
 1345    [ 'Janus: using venv from ~p'-[Dir] ].
 1346message(venv(no_site_package_dir(VEnvDir, Dir))) -->
 1347    [ 'Janus: venv dirrectory ~p does not contain ~p'-[VEnvDir, Dir] ].
 1348message(py_shell(no_janus)) -->
 1349    [ 'Janus: py_shell/0: Importing janus into the Python shell requires Python 3.10 or later.', nl,
 1350      'Run "', ansi(code, 'from janus import *', []), '" in the Python shell to import janus.'
 1351    ].
 1352message(add_cwd) -->
 1353    [ 'Interactive session; added `.` to Python `sys.path`'-[] ]