View source with formatted 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)]).  139
  140/** <module> Call Python from Prolog
  141
  142This library implements calling Python  from   Prolog.  It  is available
  143directly from Prolog if  the  janus   package  is  bundled.  The library
  144provides access to an  _embedded_  Python   instance.  If  SWI-Prolog is
  145embedded into Python  using  the   Python  package  ``janus-swi``,  this
  146library is provided either from Prolog or from the Python package.
  147
  148Normally,  the  Prolog  user  can  simply  start  calling  Python  using
  149py_call/2 or friends. In special cases it   may  be needed to initialize
  150Python with options using  py_initialize/3   and  optionally  the Python
  151search path may be extended using py_add_lib_dir/1.
  152*/
  153
  154%!  py_version is det.
  155%
  156%   Print version  info on the  embedded Python installation  based on
  157%   Python `sys.version`.  If a Python _virtual environment_ (venv) is
  158%   active, indicate this with the location of this environment found.
  159
  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    ).
  168
  169
  170%!  py_call(+Call) is det.
  171%!  py_call(+Call, -Return) is det.
  172%!  py_call(+Call, -Return, +Options) is det.
  173%
  174%   Call Python and return the result of   the called function. Call has
  175%   the shape `[Target][:Action]*`, where `Target`   is  either a Python
  176%   module name or a Python object reference. Each `Action` is either an
  177%   atom to get the denoted attribute from   current `Target` or it is a
  178%   compound term where the first  argument   is  the function or method
  179%   name  and  the  arguments  provide  the  parameters  to  the  Python
  180%   function. On success, the returned Python   object  is translated to
  181%   Prolog.  `Action` without a `Target` denotes a buit-in function.
  182%
  183%   Arguments to Python  functions  use   the  Python  conventions. Both
  184%   _positional_  and  _keyword_  arguments    are   supported.  Keyword
  185%   arguments are written as `Name = Value`   and  must appear after the
  186%   positional arguments.
  187%
  188%   Below are some examples.
  189%
  190%       % call a built-in
  191%	?- py_call(print("Hello World!\n")).
  192%	true.
  193%
  194%       % call a built-in (alternative)
  195%	?- py_call(builtins:print("Hello World!\n")).
  196%	true.
  197%
  198%	% call function in a module
  199%	?- py_call(sys:getsizeof([1,2,3]), Size).
  200%	Size = 80.
  201%
  202%	% call function on an attribute of a module
  203%       ?- py_call(sys:path:append("/home/bob/janus")).
  204%       true
  205%
  206%       % get attribute from a module
  207%       ?- py_call(sys:path, Path)
  208%       Path = ["dir1", "dir2", ...]
  209%
  210%   Given a class in a file `dog.py`  such as the following example from
  211%   the Python documentation
  212%
  213%   ```
  214%   class Dog:
  215%       tricks = []
  216%
  217%       def __init__(self, name):
  218%           self.name = name
  219%
  220%       def add_trick(self, trick):
  221%           self.tricks.append(trick)
  222%   ```
  223%
  224%   We can interact with this class as  below. Note that ``$Doc`` in the
  225%   SWI-Prolog toplevel refers to the  last   toplevel  binding  for the
  226%   variable `Dog`.
  227%
  228%       ?- py_call(dog:'Dog'("Fido"), Dog).
  229%       Dog = <py_Dog>(0x7f095c9d02e0).
  230%
  231%       ?- py_call($Dog:add_trick("roll_over")).
  232%       Dog = <py_Dog>(0x7f095c9d02e0).
  233%
  234%       ?- py_call($Dog:tricks, Tricks).
  235%       Dog = <py_Dog>(0x7f095c9d02e0),
  236%       Tricks = ["roll_over"]
  237%
  238%   If the principal term of the   first  argument is not `Target:Func`,
  239%   The argument is evaluated as the initial target, i.e., it must be an
  240%   object reference or a module.   For example:
  241%
  242%       ?- py_call(dog:'Dog'("Fido"), Dog),
  243%          py_call(Dog, X).
  244%          Dog = X, X = <py_Dog>(0x7fa8cbd12050).
  245%       ?- py_call(sys, S).
  246%          S = <py_module>(0x7fa8cd582390).
  247%
  248%   Options processed:
  249%
  250%     - py_object(Boolean)
  251%       If `true` (default `false`), translate the return as a Python
  252%       object reference. Some objects are _always_ translated to
  253%       Prolog, regardless of this flag.  These are the Python constants
  254%       ``None``, ``True`` and ``False`` as well as instances of the
  255%       Python base classes `int`, `float`, `str` or `tuple`. Instances
  256%       of sub classes of these base classes are controlled by this
  257%       option.
  258%     - py_string_as(+Type)
  259%       If Type is `atom` (default), translate a Python String into a
  260%       Prolog atom.  If Type is `string`, translate into a Prolog string.
  261%	Strings are more efficient if they are short lived.
  262%     - py_dict_as(+Type)
  263%       One of `dict` (default) to map a Python dict to a SWI-Prolog
  264%       dict if all keys can be represented.  If `{}` or not all keys
  265%       can be represented, Return is unified to a term `{k:v, ...}`
  266%       or `py({})` if the Python dict is empty.
  267%
  268%   @compat  PIP.  The  options  `py_string_as`   and  `py_dict_as`  are
  269%   SWI-Prolog  specific,  where  SWI-Prolog   Janus  represents  Python
  270%   strings as atoms as required by  the   PIP  and it represents Python
  271%   dicts by default  as  SWI-Prolog   dicts.  The  predicates values/3,
  272%   keys/2, etc. provide portable access to the data in the dict.
  273
  274%!  py_iter(+Iterator, -Value) is nondet.
  275%!  py_iter(+Iterator, -Value, +Options) is nondet.
  276%
  277%   True when Value is returned by the Python Iterator. Python iterators
  278%   may be used to implement   non-deterministic foreign predicates. The
  279%   implementation uses these steps:
  280%
  281%     1. Evaluate Iterator as py_call/2 evaluates its first argument,
  282%        except the ``Obj:Attr = Value`` construct is not accepted.
  283%     2. Call ``__iter__`` on the result to get the iterator itself.
  284%     3. Get the ``__next__`` function of the iterator.
  285%     4. Loop over the return values of the _next_ function.  If
  286%        the Python return value unifies with Value, succeed with
  287%        a choicepoint.  Abort on Python or unification exceptions.
  288%     5. Re-satisfaction continues at (4).
  289%
  290%   The example below uses the built-in iterator range():
  291%
  292%       ?- py_iter(range(1,3), X).
  293%       X = 1 ;
  294%       X = 2.
  295%
  296%   Note that the implementation performs a   _look  ahead_, i.e., after
  297%   successful unification it calls `__next__()`   again. On failure the
  298%   Prolog predicate succeeds deterministically. On   success,  the next
  299%   candidate is stored.
  300%
  301%   Note that a Python _generator_ is   a  Python _iterator_. Therefore,
  302%   given  the  Python  generator   expression    below,   we   can  use
  303%   py_iter(squares(1,5),X) to generate the squares on backtracking.
  304%
  305%   ```
  306%   def squares(start, stop):
  307%        for i in range(start, stop):
  308%            yield i * i
  309%   ```
  310%
  311%   @arg Options is processed as with py_call/3.
  312%   @bug Iterator may not depend on janus.query(), i.e., it is not
  313%   possible to iterate over a Python iterator that under the hoods
  314%   relies on a Prolog non-deterministic predicate.
  315%   @compat PIP.  The same remarks as for py_call/2 apply.
  316
  317%!  py_setattr(+Target, +Name, +Value) is det.
  318%
  319%   Set a Python attribute on an object.  If   Target  is an atom, it is
  320%   interpreted  as  a  module.  Otherwise  it  is  normally  an  object
  321%   reference. py_setattr/3 allows for  _chaining_   and  behaves  as if
  322%   defined as
  323%
  324%       py_setattr(Target, Name, Value) :-
  325%           py_call(Target, Obj, [py_object(true)]),
  326%           py_call(setattr(Obj, Name, Value)).
  327%
  328%   @compat PIP
  329
  330%!  py_run(+String, +Globals, +Locals, -Result, +Options) is det.
  331%
  332%   Interface  to  Py_CompileString()  followed   by  PyEval_EvalCode().
  333%   Options:
  334%
  335%       - file_name(String)
  336%         Errors are reported against this pseudo file name
  337%       - start(Token)
  338%         One of `eval`, `file` (default) or `single`.
  339%
  340%   @arg Globals is a dict
  341%   @arg Locals is a dict
  342
  343%!  py_is_object(@Term) is semidet.
  344%
  345%   True when Term is a Python object reference. Fails silently if Term
  346%   is any other Prolog term.
  347%
  348%   @error existence_error(py_object, Term) is raised of Term is a
  349%   Python object, but it has been freed using py_free/1.
  350%
  351%   @compat PIP. The SWI-Prolog implementation is safe in the sense that
  352%   an arbitrary term cannot be confused  with   a  Python  object and a
  353%   reliable error is generated  if  the   references  has  been  freed.
  354%   Portable applications can not rely on this.
  355
  356%!  py_is_dict(@Term) is semidet.
  357%
  358%   True if Term is a Prolog term that represents a Python dict.
  359%
  360%   @compat PIP. The SWI-Prolog version accepts   both a SWI-Prolog dict
  361%   and the `{k:v,...}`  representation.  See   `py_dict_as`  option  of
  362%   py_call/2.
  363
  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).
  371
  372
  373%!  py_free(+Obj) is det.
  374%
  375%   Immediately free (decrement the  reference   count)  for  the Python
  376%   object Obj. Further reference  to  Obj   using  e.g.,  py_call/2  or
  377%   py_free/1 raises an `existence_error`. Note that by decrementing the
  378%   reference count, we make the reference invalid from Prolog. This may
  379%   not  actually  delete  the  object  because   the  object  may  have
  380%   references inside Python.
  381%
  382%   Prolog references to Python objects  are   subject  to  atom garbage
  383%   collection and thus normally do not need to be freed explicitly.
  384%
  385%   @compat PIP. The SWI-Prolog  implementation   is  safe  and normally
  386%   reclaiming Python object can  be  left   to  the  garbage collector.
  387%   Portable applications may not assume   garbage  collection of Python
  388%   objects and must ensure to call py_free/1 exactly once on any Python
  389%   object reference. Not calling  py_free/1   leaks  the Python object.
  390%   Calling it twice may lead to undefined behavior.
  391
  392%!  py_with_gil(:Goal) is semidet.
  393%
  394%   Run Goal as  once(Goal)  while  holding   the  Phyton  GIL  (_Global
  395%   Interpreter Lock_). Note that  all   predicates  that  interact with
  396%   Python lock the GIL. This predicate is   only required if we wish to
  397%   make multiple calls to Python while keeping   the  GIL. The GIL is a
  398%   _recursive_ lock and thus calling py_call/1,2  while holding the GIL
  399%   does not _deadlock_.
  400
  401%!  py_gil_owner(-Thread) is semidet.
  402%
  403%   True when  the Python GIL is  owned by Thread.  Note  that, unless
  404%   Thread  is the  calling thread,  this merely  samples the  current
  405%   state and may thus no longer  be true when the predicate succeeds.
  406%   This predicate is intended to help diagnose _deadlock_ problems.
  407%
  408%   Note that  this predicate returns  the Prolog threads  that locked
  409%   the GIL.  It is however possible that Python releases the GIL, for
  410%   example if  it performs a  blocking call.  In this  scenario, some
  411%   other thread or no thread may hold the gil.
  412
  413
  414		 /*******************************
  415		 *         COMPATIBILIY		*
  416		 *******************************/
  417
  418%!  py_func(+Module, +Function, -Return) is det.
  419%!  py_func(+Module, +Function, -Return, +Options) is det.
  420%
  421%   Call Python Function in  Module.   The  SWI-Prolog implementation is
  422%   equivalent to py_call(Module:Function, Return).   See  py_call/2 for
  423%   details.
  424%
  425%   @compat  PIP.  See  py_call/2  for  notes.    Note   that,  as  this
  426%   implementation is based on py_call/2,   Function can use _chaining_,
  427%   e.g., py_func(sys, path:append(dir), Return)  is   accepted  by this
  428%   implementation, but not portable.
  429
  430py_func(Module, Function, Return) :-
  431    py_call(Module:Function, Return).
  432py_func(Module, Function, Return, Options) :-
  433    py_call(Module:Function, Return, Options).
  434
  435%!  py_dot(+ObjRef, +MethAttr, -Ret) is det.
  436%!  py_dot(+ObjRef, +MethAttr, -Ret, +Options) is det.
  437%
  438%   Call a method or access  an  attribute   on  the  object ObjRef. The
  439%   SWI-Prolog implementation is equivalent  to py_call(ObjRef:MethAttr,
  440%   Return). See py_call/2 for details.
  441%
  442%   @compat PIP.  See py_func/3 for details.
  443
  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		 *******************************/
  453
  454%!  values(+Dict, +Path, ?Val) is semidet.
  455%
  456%   Get the value associated with Dict at  Path. Path is either a single
  457%   key or a list of keys.
  458%
  459%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  460%   {k:v, ...} term as well as py({k:v, ...}.
  461
  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).
  490
  491%!  keys(+Dict, ?Keys) is det.
  492%
  493%   True when Keys is a list of keys that appear in Dict.
  494%
  495%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  496%   {k:v, ...} term as well as py({k:v, ...}.
  497
  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].
  510
  511%!  key(+Dict, ?Key) is nondet.
  512%
  513%   True when Key is a key in   Dict.  Backtracking enumerates all known
  514%   keys.
  515%
  516%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  517%   {k:v, ...} term as well as py({k:v, ...}.
  518
  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).
  530
  531%!  items(+Dict, ?Items) is det.
  532%
  533%   True when Items is a list of Key:Value that appear in Dict.
  534%
  535%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  536%   {k:v, ...} term as well as py({k:v, ...}.
  537
  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		 *******************************/
  558
  559%!  py_shell
  560%
  561%   Start an interactive Python REPL  loop   using  the  embedded Python
  562%   interpreter. The interpreter first imports `janus` as below.
  563%
  564%       from janus import *
  565%
  566%   So, we can do
  567%
  568%       ?- py_shell.
  569%       ...
  570%       >>> query_once("writeln(X)", {"X":"Hello world"})
  571%       Hello world
  572%       {'truth': True}
  573%
  574%   If possible, we enable command line   editing using the GNU readline
  575%   library.
  576%
  577%   When used in an environment  where  Prolog   does  not  use the file
  578%   handles 0,1,2 for  the  standard   streams,  e.g.,  in  `swipl-win`,
  579%   Python's I/O is rebound to use  Prolog's I/O. This includes Prolog's
  580%   command line editor, resulting in  a   mixed  history  of Prolog and
  581%   Pythin commands.
  582
  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		 *******************************/
  599
  600%!  py_pp(+Term) is det.
  601%!  py_pp(+Term, +Options) is det.
  602%!  py_pp(+Stream, +Term, +Options) is det.
  603%
  604%   Pretty prints the Prolog translation of a Python data structure in
  605%   Python  syntax. This  exploits  pformat() from  the Python  module
  606%   `pprint` to do the actual  formatting.  Options is translated into
  607%   keyword arguments  passed to  pprint.pformat().  In  addition, the
  608%   option  nl(Bool)  is processed.   When  `true`  (default), we  use
  609%   pprint.pp(), which  makes the output  followed by a  newline.  For
  610%   example:
  611%
  612%   ```
  613%   ?- py_pp(py{a:1, l:[1,2,3], size:1000000},
  614%            [underscore_numbers(true)]).
  615%   {'a': 1, 'l': [1, 2, 3], 'size': 1_000_000}
  616%   ```
  617%
  618%   @compat PIP
  619
  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).
  643
  644
  645%!  py_object_dir(+ObjRef, -List) is det.
  646%!  py_object_dict(+ObjRef, -Dict) is det.
  647%
  648%   Examine attributes of  an  object.   The  predicate  py_object_dir/2
  649%   fetches the names of all attributes,   while  py_object_dir/2 gets a
  650%   dict with all attributes and their values.
  651%
  652%   @compat PIP
  653
  654py_object_dir(ObjRef, List) :-
  655    py_call(ObjRef:'__dir__'(), List).
  656
  657py_object_dict(ObjRef, Dict) :-
  658    py_call(ObjRef:'__dict__', Dict).
  659
  660%!  py_obj_dir(+ObjRef, -List) is det.
  661%!  py_obj_dict(+ObjRef, -Dict) is det.
  662%
  663%   @deprecated Use py_object_dir/2 or py_object_dict/2.
  664
  665py_obj_dir(ObjRef, List) :-
  666    py_object_dir(ObjRef, List).
  667
  668py_obj_dict(ObjRef, Dict) :-
  669    py_object_dict(ObjRef, Dict).
  670
  671
  672%!  py_type(+ObjRef, -Type:atom) is det.
  673%
  674%   True when Type is the name of the   type of ObjRef. This is the same
  675%   as ``type(ObjRef).__name__`` in Python.
  676%
  677%   @compat PIP
  678
  679py_type(ObjRef, Type) :-
  680    py_call(type(ObjRef):'__name__', Type).
  681
  682%!  py_isinstance(+ObjRef, +Type) is semidet.
  683%
  684%   True if ObjRef is an instance of Type   or an instance of one of the
  685%   sub types of Type. This  is   the  same as ``isinstance(ObjRef)`` in
  686%   Python.
  687%
  688%   @arg Type is either a term `Module:Type` or a plain atom to refer to
  689%   a built-in type.
  690%
  691%   @compat PIP
  692
  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).
  697
  698%!  py_module_exists(+Module) is semidet.
  699%
  700%   True if Module is a currently  loaded   Python  module  or it can be
  701%   loaded.
  702%
  703%   @compat PIP
  704
  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).
  713
  714%!  py_hasattr(+ModuleOrObj, ?Name) is nondet.
  715%
  716%   True when Name is an attribute of   Module. The name is derived from
  717%   the Python built-in hasattr(). If Name   is unbound, this enumerates
  718%   the members of py_object_dir/2.
  719%
  720%   @arg ModuleOrObj If this is an atom it refers to a module, otherwise
  721%   it must be a Python object reference.
  722%
  723%   @compat PIP
  724
  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    ).
  737
  738
  739%!  py_import(+Spec, +Options) is det.
  740%
  741%   Import a Python module.  Janus   imports  modules automatically when
  742%   referred in py_call/2 and  related   predicates.  Importing a module
  743%   implies  the  module  is  loaded   using  Python's  ``__import__()``
  744%   built-in and added to a table  that   maps  Prolog atoms to imported
  745%   modules. This predicate explicitly imports a module and allows it to
  746%   be associated with a different  name.   This  is  useful for loading
  747%   _nested modules_, i.e., a specific module   from a Python package as
  748%   well as for  avoiding  conflicts.  For   example,  with  the  Python
  749%   `selenium` package installed, we can do in Python:
  750%
  751%       >>> from selenium import webdriver
  752%       >>> browser = webdriver.Chrome()
  753%
  754%   Without this predicate, we can do
  755%
  756%       ?- py_call('selenium.webdriver':'Chrome'(), Chrome).
  757%
  758%   For a single call this is  fine,   but  for making multiple calls it
  759%   gets cumbersome.  With this predicate we can write this.
  760%
  761%       ?- py_import('selenium.webdriver', []).
  762%       ?- py_call(webdriver:'Chrome'(), Chrome).
  763%
  764%   By default, the imported module  is   associated  to an atom created
  765%   from the last segment of the dotted   name. Below we use an explicit
  766%   name.
  767%
  768%       ?- py_import('selenium.webdriver', [as(browser)]).
  769%       ?- py_call(browser:'Chrome'(), Chrome).
  770%
  771%   @error  permission_error(import_as,  py_module,  As)   if  there  is
  772%   already a module associated with As.
  773
  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]).
  783
  784%!  py_module(+Module:atom, +Source:string) is det.
  785%
  786%   Load Source into the Python module Module.   This  is intended to be
  787%   used together with the `string` _quasi quotation_ that supports long
  788%   strings in SWI-Prolog.   For example:
  789%
  790%   ```
  791%   :- use_module(library(strings)).
  792%   :- py_module(hello,
  793%                {|string||
  794%                 | def say_hello_to(s):
  795%                 |     print(f"hello {s}")
  796%                 |}).
  797%   ```
  798%
  799%   Calling this predicate multiple  times  with   the  same  Module and
  800%   Source is a no-op. Called with  a   different  source  creates a new
  801%   Python module that replaces the old in the global namespace.
  802%
  803%   @error python_error(Type, Data) is raised if Python raises an error.
  804
  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').
  898
  899%!  py_initialize(+Program, +Argv, +Options) is det.
  900%
  901%   Initialize  and configure  the  embedded Python  system.  If  this
  902%   predicate is  not called before any  other call to Python  such as
  903%   py_call/2, it is called _lazily_, passing the Prolog executable as
  904%   Program, passing Argv from the  Prolog flag `py_argv` and an empty
  905%   Options list.
  906%
  907%   Calling this predicate while the  Python is already initialized is
  908%   a  no-op.  This  predicate is  thread-safe, where  the first  call
  909%   initializes Python.
  910%
  911%   In addition to initializing the Python system, it
  912%
  913%     - Adds the directory holding `janus.py` to the Python module
  914%       search path.
  915%     - If Prolog I/O is not connected to the file handles 0,1,2,
  916%       it rebinds Python I/O to use the Prolog I/O.
  917%
  918%   @arg Options is currently ignored.  It will be used to provide
  919%   additional configuration options.
  920
  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    ).
  932
  933%!  py_connect_io is det.
  934%
  935%   If SWI-Prolog console streams are bound to something non-standard,
  936%   bind the Python console I/O to our streans.
  937
  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		 *******************************/
  954
  955%!  py_lib_dirs(-Dirs) is det.
  956%
  957%   True when Dirs is a list of directories searched for Python modules.
  958%   The elements of Dirs are in Prolog canonical notation.
  959%
  960%   @compat PIP
  961
  962py_lib_dirs(Dirs) :-
  963    py_call(sys:path, Dirs0),
  964    maplist(prolog_to_os_filename, Dirs, Dirs0).
  965
  966%!  py_add_lib_dir(+Dir) is det.
  967%!  py_add_lib_dir(+Dir, +Where) is det.
  968%
  969%   Add a directory to the Python  module   search  path.  In the second
  970%   form, Where is one of `first`   or `last`. py_add_lib_dir/1 adds the
  971%   directory as `last`. The property `sys:path`   is not modified if it
  972%   already contains Dir.
  973%
  974%   Dir is in Prolog notation. The added   directory  is converted to an
  975%   absolute path using the OS notation using prolog_to_os_filename/2.
  976%
  977%   If Dir is a _relative_ path, it   is taken relative to Prolog source
  978%   file when used as a _directive_ and  relative to the process working
  979%   directory when called as a predicate.
  980%
  981%   @compat PIP. Note  that  SWI-Prolog   uses  POSIX  file  conventions
  982%   internally, mapping to OS  conventions   inside  the predicates that
  983%   deal with files or explicitly   using prolog_to_os_filename/2. Other
  984%   systems may use the native file conventions in Prolog.
  985
  986:- multifile system:term_expansion/2.  987
  988system:term_expansion((:- py_add_lib_dir(Dir0)),
  989                      (:- initialization(py_add_lib_dir(Dir, first), now))) :-
  990    \+ is_absolute_file_name(Dir0),
  991    prolog_load_context(directory, CWD),
  992    absolute_file_name(Dir0, Dir, [relative_to(CWD)]).
  993system:term_expansion((:- py_add_lib_dir(Dir0, Where)),
  994                      (:- initialization(py_add_lib_dir(Dir, Where), now))) :-
  995    \+ is_absolute_file_name(Dir0),
  996    prolog_load_context(directory, CWD),
  997    absolute_file_name(Dir0, Dir, [relative_to(CWD)]),
  998    absolute_file_name(Dir0, Dir).
  999
 1000py_add_lib_dir(Dir) :-
 1001    py_add_lib_dir(Dir, last).
 1002
 1003py_add_lib_dir(Dir, Where) :-
 1004    absolute_file_name(Dir, AbsDir),
 1005    prolog_to_os_filename(AbsDir, OSDir),
 1006    py_add_lib_dir_(OSDir, Where).
 1007
 1008py_add_lib_dir_(OSDir, Where) :-
 1009    (   py_call(sys:path, Dirs0),
 1010        memberchk(OSDir, Dirs0)
 1011    ->  true
 1012    ;   Where == last
 1013    ->  py_call(sys:path:append(OSDir), _)
 1014    ;   Where == first
 1015    ->  py_call(sys:path:insert(0, OSDir), _)
 1016    ;   must_be(oneof([first,last]), Where)
 1017    ).
 1018
 1019:- det(repl_add_cwd/0). 1020repl_add_cwd :-
 1021    current_prolog_flag(break_level, Level),
 1022    Level >= 0,
 1023    !,
 1024    (   py_call(sys:path:count(''), N),
 1025        N > 0
 1026    ->  true
 1027    ;   print_message(informational, janus(add_cwd)),
 1028        py_add_lib_dir_('', first)
 1029    ).
 1030repl_add_cwd.
 1031
 1032:- multifile
 1033    prolog:repl_loop_hook/2. 1034
 1035prolog:repl_loop_hook(begin, Level) :-
 1036    Level >= 0,
 1037    py_is_initialized,
 1038    repl_add_cwd.
 1039
 1040
 1041		 /*******************************
 1042		 *           CALLBACK		*
 1043		 *******************************/
 1044
 1045:- dynamic py_call_cache/8 as volatile. 1046
 1047:- meta_predicate py_call_string(:, +, -). 1048
 1049%   py_call_string(:String, +DictIn, -Dict) is nondet.
 1050%
 1051%   Support janus.query_once() and janus.query(). Parses   String  into a goal
 1052%   term. Next, all variables from the goal   term that appear in DictIn
 1053%   are bound to the value from  this   dict.  Dict  is created from the
 1054%   remaining variables, unless they  start   with  an underscore (e.g.,
 1055%   `_Time`) and the key `truth. On   success,  the Dict values contain
 1056%   the bindings from the  answer  and   `truth`  is  either  `true` or
 1057%   `Undefined`. On failure, the Dict values are bound to `None` and the
 1058%   `truth` is `false`.
 1059%
 1060%   Parsing and distributing the variables over the two dicts is cached.
 1061
 1062py_call_string(M:String, Input, Dict) :-
 1063    py_call_cache(String, Input, TV, M, Goal, Dict, Truth, OutVars),
 1064    !,
 1065    py_call(TV, M:Goal, Truth, OutVars).
 1066py_call_string(M:String, Input, Dict) :-
 1067    term_string(Goal, String, [variable_names(Map)]),
 1068    unbind_dict(Input, VInput),
 1069    exclude(not_in_projection(VInput), Map, OutBindings),
 1070    dict_create(Dict, bindings, [truth=Truth|OutBindings]),
 1071    maplist(arg(2), OutBindings, OutVars),
 1072    TV = Input.get(truth, 'PLAIN_TRUTHVALS'),
 1073    asserta(py_call_cache(String, VInput, TV, M, Goal, Dict, Truth, OutVars)),
 1074    VInput = Input,
 1075    py_call(TV, M:Goal, Truth, OutVars).
 1076
 1077py_call('NO_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1078    (   call(M:Goal)
 1079    *-> bind_status_no_no_truthvals(Truth)
 1080    ;   Truth = @false,
 1081	maplist(bind_none, OutVars)
 1082    ).
 1083py_call('PLAIN_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1084    (   call(M:Goal)
 1085    *-> bind_status_plain_truthvals(Truth)
 1086    ;   Truth = @false,
 1087	maplist(bind_none, OutVars)
 1088    ).
 1089py_call('DELAY_LISTS', M:Goal, Truth, OutVars) =>
 1090    (   call_delays(M:Goal, Delays)
 1091    *-> bind_status_delay_lists(Delays, Truth)
 1092    ;   Truth = @false,
 1093	maplist(bind_none, OutVars)
 1094    ).
 1095py_call('RESIDUAL_PROGRAM', M:Goal, Truth, OutVars) =>
 1096    (   call_delays(M:Goal, Delays)
 1097    *-> bind_status_residual_program(Delays, Truth)
 1098    ;   Truth = @false,
 1099	maplist(bind_none, OutVars)
 1100    ).
 1101
 1102not_in_projection(Input, Name=Value) :-
 1103    (   get_dict(Name, Input, Value)
 1104    ->  true
 1105    ;   sub_atom(Name, 0, _, _, '_')
 1106    ).
 1107
 1108bind_none(@none).
 1109
 1110bind_status_no_no_truthvals(@true).
 1111
 1112bind_status_plain_truthvals(Truth) =>
 1113    (   '$tbl_delay_list'([])
 1114    ->  Truth = @true
 1115    ;   py_undefined(Truth)
 1116    ).
 1117
 1118bind_status_delay_lists(true, Truth) =>
 1119    Truth = @true.
 1120bind_status_delay_lists(Delays, Truth) =>
 1121    py_call(janus:'Undefined'(prolog(Delays)), Truth).
 1122
 1123bind_status_residual_program(true, Truth) =>
 1124    Truth = @true.
 1125bind_status_residual_program(Delays, Truth) =>
 1126    delays_residual_program(Delays, Program),
 1127    py_call(janus:'Undefined'(prolog(Program)), Truth).
 1128
 1129py_undefined(X) :-
 1130    py_call(janus:undefined, X).
 1131
 1132unbind_dict(Dict0, Dict) :-
 1133    dict_pairs(Dict0, Tag, Pairs0),
 1134    maplist(unbind, Pairs0, Pairs),
 1135    dict_pairs(Dict, Tag, Pairs).
 1136
 1137unbind(Name-_, Name-_) :-
 1138    sub_atom(Name, 0, 1, _, Char1),
 1139    char_type(Char1, prolog_var_start),
 1140    !.
 1141unbind(NonVar, NonVar).
 1142
 1143
 1144		 /*******************************
 1145		 *     SUPPORT PYTHON CALLS     *
 1146		 *******************************/
 1147
 1148:- public
 1149       px_cmd/3,
 1150       px_call/4,
 1151       px_comp/7. 1152
 1153% These predicates are helpers  for the corresponding Python functions
 1154% in janus.py.
 1155
 1156
 1157%   px_call(+Input:tuple, +Module, -Pred, -Ret)
 1158%
 1159%   Supports  px_qdet()  and  apply().  Note    that   these  predicates
 1160%   explicitly address predicates  in  a   particular  module.  For meta
 1161%   predicates, this implies they also control  the context module. This
 1162%   leads to ``janus.cmd("consult", "consult", file)`` to consult _file_
 1163%   into the module `consult`, which is not   what we want. Therefore we
 1164%   set the context module to `user`, which is better, but probably also
 1165%   not what we want.
 1166
 1167px_call(-(), Module, Pred, Ret) =>
 1168    @(call(Module:Pred, Ret), user).
 1169px_call(-(A1), Module, Pred, Ret) =>
 1170    @(call(Module:Pred, A1, Ret), user).
 1171px_call(-(A1,A2), Module, Pred, Ret) =>
 1172    @(call(Module:Pred, A1, A2, Ret), user).
 1173px_call(-(A1,A2,A3), Module, Pred, Ret) =>
 1174    @(call(Module:Pred, A1, A2, A3, Ret), user).
 1175px_call(-(A1,A2,A3,A4), Module, Pred, Ret) =>
 1176    @(call(Module:Pred, A1, A2, A3, A4, Ret), user).
 1177px_call(Tuple, Module, Pred, Ret) =>
 1178    compound_name_arguments(Tuple, _, Args),
 1179    append(Args, [Ret], GArgs),
 1180    Goal =.. [Pred|GArgs],
 1181    @(Module:Goal, user).
 1182
 1183px_cmd(Module, Pred, Tuple) :-
 1184    (   compound(Tuple)
 1185    ->  compound_name_arguments(Tuple, _, Args),
 1186	Goal =.. [Pred|Args]
 1187    ;   Goal = Pred
 1188    ),
 1189    @(Module:Goal, user).
 1190
 1191px_comp(Module, Pred, Tuple, Vars, Set, TV, Ret) :-
 1192    length(Out, Vars),
 1193    (   compound(Tuple)
 1194    ->  compound_name_arguments(Tuple, _, Args),
 1195	append(Args, Out, GArgs),
 1196	Goal =.. [Pred|GArgs]
 1197    ;   Goal =.. [Pred|Out]
 1198    ),
 1199    compound_name_arguments(OTempl0, -, Out),
 1200    tv_goal_and_template(TV, @(Module:Goal, user), FGoal, OTempl0, OTempl),
 1201    findall(OTempl, FGoal, Ret0),
 1202    (   Set == @true
 1203    ->  sort(Ret0, Ret)
 1204    ;   Ret = Ret0
 1205    ).
 1206
 1207:- meta_predicate
 1208    call_delays_py(0, -). 1209
 1210% 0,1,2: TruthVal(Enum) from janus.py
 1211tv_goal_and_template('NO_TRUTHVALS',
 1212                     Goal, Goal, Templ, Templ) :- !.
 1213tv_goal_and_template('PLAIN_TRUTHVALS',
 1214                     Goal, ucall(Goal, TV), Templ, -(Templ,TV)) :- !.
 1215tv_goal_and_template('DELAY_LISTS',
 1216                     Goal, call_delays_py(Goal, TV), Templ, -(Templ,TV)) :- !.
 1217tv_goal_and_template(Mode, _, _, _, _) :-
 1218    domain_error("px_comp() truth", Mode).
 1219
 1220:- public
 1221    ucall/2,
 1222    call_delays_py/2. 1223
 1224ucall(Goal, TV) :-
 1225    call(Goal),
 1226    (   '$tbl_delay_list'([])
 1227    ->  TV = 1
 1228    ;   TV = 2
 1229    ).
 1230
 1231call_delays_py(Goal, PyDelays) :-
 1232    call_delays(Goal, Delays),
 1233    (   Delays == true
 1234    ->  PyDelays = []
 1235    ;   comma_list(Delays, Array),
 1236        maplist(term_string, Array, PyDelays)
 1237    ).
 1238
 1239
 1240		 /*******************************
 1241		 *          PYTHON I/O          *
 1242		 *******************************/
 1243
 1244%   py_write(+Stream, -String) is det.
 1245%   py_readline(+Stream, +Size, +Prompt, +Line) is det.
 1246%
 1247%   Called from redefined Python console  I/O   to  write/read using the
 1248%   Prolog streams.
 1249
 1250:- '$hide'((py_write/1,
 1251	    py_readline/4)). 1252
 1253py_write(Stream, String) :-
 1254    notrace(format(Stream, '~s', [String])).
 1255
 1256py_readline(Stream, Size, Prompt, Line) :-
 1257    notrace(py_readline_(Stream, Size, Prompt, Line)).
 1258
 1259py_readline_(Stream, _Size, Prompt, Line) :-
 1260    prompt1(Prompt),
 1261    read_line_to_string(Stream, Read),
 1262    (   Read == end_of_file
 1263    ->  Line = ""
 1264    ;   string_concat(Read, "\n", Line),
 1265	py_add_history(Read)
 1266    ).
 1267
 1268py_add_history(Line) :-
 1269    ignore(catch(prolog:history(user_input, add(Line)), _, true)).
 1270
 1271
 1272		 /*******************************
 1273		 *          COMPILING           *
 1274		 *******************************/
 1275
 1276%   py_consult(+File, +Data, +Module) is det.
 1277%
 1278%   Support janus.consult(file, data=None, module='user').
 1279
 1280:- public py_consult/3. 1281py_consult(File, @none, Module) =>
 1282    consult(Module:File).
 1283py_consult(File, Data, Module) =>
 1284    setup_call_cleanup(
 1285	open_string(Data, In),
 1286	load_files(Module:File, [stream(In)]),
 1287	close(In)).
 1288
 1289
 1290		 /*******************************
 1291		 *           MESSAGES		*
 1292		 *******************************/
 1293
 1294:- multifile
 1295    prolog:error_message//1,
 1296    prolog:message_context//1,
 1297    prolog:message//1. 1298
 1299prolog:error_message(python_error(Class, Value)) -->
 1300    { py_str(Value, Message)
 1301    },
 1302    [ 'Python ', ansi(code, "'~w'", [Class]), ':', nl,
 1303      '  ~w'-[Message]
 1304    ].
 1305prolog:error_message(permission_error(import_as, py_module, As)) -->
 1306    [ 'Janus: No permission to import a module as ', ansi(code, '~q', As),
 1307      ': module exists.'
 1308    ].
 1309
 1310prolog:message_context(context(_, PythonCtx)) -->
 1311    { nonvar(PythonCtx),
 1312      PythonCtx = python_stack(Stack),
 1313      current_prolog_flag(py_backtrace, true),
 1314      py_is_object(Stack),
 1315      !,
 1316      current_prolog_flag(py_backtrace_depth, Depth),
 1317      py_call(traceback:format_tb(Stack, Depth), Frames)
 1318    },
 1319    [ nl, 'Python stack:', nl ],
 1320    sequence(py_stack_frame, Frames).
 1321
 1322py_stack_frame(String) -->
 1323    { split_string(String, "\n", "", Lines)
 1324    },
 1325    sequence(msg_line, [nl], Lines).
 1326
 1327msg_line(Line) -->
 1328    [ '~s'-[Line] ].
 1329
 1330prolog:message(janus(Msg)) -->
 1331    message(Msg).
 1332
 1333message(version(Janus, Python)) -->
 1334    [ 'Janus ~w embeds Python ~w'-[Janus, Python] ].
 1335message(venv(Dir, _EnvSiteDir)) -->
 1336    [ 'Janus: using venv from ~p'-[Dir] ].
 1337message(venv(no_site_package_dir(VEnvDir, Dir))) -->
 1338    [ 'Janus: venv dirrectory ~p does not contain ~p'-[VEnvDir, Dir] ].
 1339message(py_shell(no_janus)) -->
 1340    [ 'Janus: py_shell/0: Importing janus into the Python shell requires Python 3.10 or later.', nl,
 1341      'Run "', ansi(code, 'from janus import *', []), '" in the Python shell to import janus.'
 1342    ].
 1343message(add_cwd) -->
 1344    [ 'Interactive session; added `.` to Python `sys.path`'-[] ]