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, 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/4,                   % +Module, +ObjRef, +Meth, ?Ret
   53            py_dot/5,                   % +Module, +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_module/2,                % +Module:atom, +Source:string
   76
   77            py_initialize/3,            % +Program, +Argv, +Options
   78            py_lib_dirs/1,              % -Dirs
   79            py_add_lib_dir/1,           % +Dir
   80            py_add_lib_dir/2,           % +Dir,+Where
   81
   82            op(200, fy, @),             % @constant
   83            op(50,  fx, #)              % #Value
   84          ]).   85:- meta_predicate py_with_gil(0).   86
   87:- use_module(library(apply_macros), []).   88:- autoload(library(lists), [append/3, member/2]).   89:- autoload(library(apply), [maplist/2, exclude/3, maplist/3]).   90:- autoload(library(error), [must_be/2, domain_error/2]).   91:- autoload(library(dicts), [dict_keys/2]).   92:- autoload(library(option), [dict_options/2]).   93:- autoload(library(prolog_code), [comma_list/2]).   94:- autoload(library(readutil), [read_line_to_string/2]).   95:- autoload(library(wfs), [call_delays/2, delays_residual_program/2]).   96:- autoload(library(dcg/high_order), [sequence//2, sequence//3]).   97
   98:- if(\+current_predicate(py_call/1)).   99:- if(current_prolog_flag(windows, true)).  100:- use_module(library(shlib), [win_add_dll_directory/1]).  101
  102% Just having the Python dir in PATH seems insufficient. We also need to
  103% add the directory to the DLL search path.
  104add_python_dll_dir :-
  105    absolute_file_name(path('python3.dll'), DLL, [access(read)]),
  106    file_directory_name(DLL, Dir),
  107    win_add_dll_directory(Dir).
  108:- initialization(add_python_dll_dir, now).  109:- endif.  110
  111:- use_foreign_library(foreign(janus), [visibility(global)]).  112:- endif.  113
  114:- predicate_options(py_call/3, 3,
  115                     [ py_object(boolean),
  116                       py_string_as(oneof([string,atom]))
  117                     ]).  118:- predicate_options(py_func/4, 4,
  119                     [ pass_to(py_call/3, 3)
  120                     ]).  121:- predicate_options(py_dot/5, 5,
  122                     [ pass_to(py_call/3, 3)
  123                     ]).  124
  125:- public
  126    py_initialize/0,
  127    py_call_string/3,
  128    py_write/2,
  129    py_readline/4.  130
  131:- create_prolog_flag(py_backtrace,       true, [type(boolean), keep(true)]).  132:- create_prolog_flag(py_backtrace_depth, 4,    [type(integer), keep(true)]).  133:- create_prolog_flag(py_argv,		  [],   [type(term), keep(true)]).  134
  135/** <module> Call Python from Prolog
  136
  137This library implements calling Python  from   Prolog.  It  is available
  138directly from Prolog if  the  janus   package  is  bundled.  The library
  139provides access to an  _embedded_  Python   instance.  If  SWI-Prolog is
  140embedded into Python  using  the   Python  package  ``janus-swi``,  this
  141library is provided either from Prolog or from the Python package.
  142
  143Normally,  the  Prolog  user  can  simply  start  calling  Python  using
  144py_call/2 or friends. In special cases it   may  be needed to initialize
  145Python with options using  py_initialize/3   and  optionally  the Python
  146search path may be extended using py_add_lib_dir/1.
  147*/
  148
  149%!  py_version is det.
  150%
  151%   Print version  info on the  embedded Python installation  based on
  152%   Python `sys.version`.  If a Python _virtual environment_ (venv) is
  153%   active, indicate this with the location of this environment found.
  154
  155py_version :-
  156    py_call(sys:version, PythonVersion),
  157    py_call(janus_swi:version_str(), JanusVersion),
  158    print_message(information, janus(version(JanusVersion, PythonVersion))),
  159    (   py_venv(VEnvDir, EnvSiteDir)
  160    ->  print_message(information, janus(venv(VEnvDir, EnvSiteDir)))
  161    ;   true
  162    ).
  163
  164
  165%!  py_call(+Call) is det.
  166%!  py_call(+Call, -Return) is det.
  167%!  py_call(+Call, -Return, +Options) is det.
  168%
  169%   Call Python and return the result of   the called function. Call has
  170%   the shape `[Target][:Action]*`, where `Target`   is  either a Python
  171%   module name or a Python object reference. Each `Action` is either an
  172%   atom to get the denoted attribute from   current `Target` or it is a
  173%   compound term where the first  argument   is  the function or method
  174%   name  and  the  arguments  provide  the  parameters  to  the  Python
  175%   function. On success, the returned Python   object  is translated to
  176%   Prolog.  `Action` without a `Target` denotes a buit-in function.
  177%
  178%   Arguments to Python  functions  use   the  Python  conventions. Both
  179%   _positional_  and  _keyword_  arguments    are   supported.  Keyword
  180%   arguments are written as `Name = Value`   and  must appear after the
  181%   positional arguments.
  182%
  183%   Below are some examples.
  184%
  185%       % call a built-in
  186%	?- py_call(print("Hello World!\n")).
  187%	true.
  188%
  189%       % call a built-in (alternative)
  190%	?- py_call(builtins:print("Hello World!\n")).
  191%	true.
  192%
  193%	% call function in a module
  194%	?- py_call(sys:getsizeof([1,2,3]), Size).
  195%	Size = 80.
  196%
  197%	% call function on an attribute of a module
  198%       ?- py_call(sys:path:append("/home/bob/janus")).
  199%       true
  200%
  201%       % get attribute from a module
  202%       ?- py_call(sys:path, Path)
  203%       Path = ["dir1", "dir2", ...]
  204%
  205%   Given a class in a file `dog.py`  such as the following example from
  206%   the Python documentation
  207%
  208%   ```
  209%   class Dog:
  210%       tricks = []
  211%
  212%       def __init__(self, name):
  213%           self.name = name
  214%
  215%       def add_trick(self, trick):
  216%           self.tricks.append(trick)
  217%   ```
  218%
  219%   We can interact with this class as  below. Note that ``$Doc`` in the
  220%   SWI-Prolog toplevel refers to the  last   toplevel  binding  for the
  221%   variable `Dog`.
  222%
  223%       ?- py_call(dog:'Dog'("Fido"), Dog).
  224%       Dog = <py_Dog>(0x7f095c9d02e0).
  225%
  226%       ?- py_call($Dog:add_trick("roll_over")).
  227%       Dog = <py_Dog>(0x7f095c9d02e0).
  228%
  229%       ?- py_call($Dog:tricks, Tricks).
  230%       Dog = <py_Dog>(0x7f095c9d02e0),
  231%       Tricks = ["roll_over"]
  232%
  233%   If the principal term of the   first  argument is not `Target:Func`,
  234%   The argument is evaluated as the initial target, i.e., it must be an
  235%   object reference or a module.   For example:
  236%
  237%       ?- py_call(dog:'Dog'("Fido"), Dog),
  238%          py_call(Dog, X).
  239%          Dog = X, X = <py_Dog>(0x7fa8cbd12050).
  240%       ?- py_call(sys, S).
  241%          S = <py_module>(0x7fa8cd582390).
  242%
  243%   Options processed:
  244%
  245%     - py_object(Boolean)
  246%       If `true` (default `false`), translate the return as a Python
  247%       object reference. Some objects are _always_ translated to
  248%       Prolog, regardless of this flag.  These are the Python constants
  249%       ``None``, ``True`` and ``False`` as well as instances of the
  250%       Python base classes `int`, `float`, `str` or `tuple`. Instances
  251%       of sub classes of these base classes are controlled by this
  252%       option.
  253%     - py_string_as(+Type)
  254%       If Type is `atom` (default), translate a Python String into a
  255%       Prolog atom.  If Type is `string`, translate into a Prolog string.
  256%	Strings are more efficient if they are short lived.
  257%     - py_dict_as(+Type)
  258%       One of `dict` (default) to map a Python dict to a SWI-Prolog
  259%       dict if all keys can be represented.  If `{}` or not all keys
  260%       can be represented, Return is unified to a term `{k:v, ...}`
  261%       or `py({})` if the Python dict is empty.
  262%
  263%   @compat  PIP.  The  options  `py_string_as`   and  `py_dict_as`  are
  264%   SWI-Prolog  specific,  where  SWI-Prolog   Janus  represents  Python
  265%   strings as atoms as required by  the   PIP  and it represents Python
  266%   dicts by default  as  SWI-Prolog   dicts.  The  predicates values/3,
  267%   keys/2, etc. provide portable access to the data in the dict.
  268
  269%!  py_iter(+Iterator, -Value) is nondet.
  270%!  py_iter(+Iterator, -Value, +Options) is nondet.
  271%
  272%   True when Value is returned by the Python Iterator. Python iterators
  273%   may be used to implement   non-deterministic foreign predicates. The
  274%   implementation uses these steps:
  275%
  276%     1. Evaluate Iterator as py_call/2 evaluates its first argument,
  277%        except the ``Obj:Attr = Value`` construct is not accepted.
  278%     2. Call ``__iter__`` on the result to get the iterator itself.
  279%     3. Get the ``__next__`` function of the iterator.
  280%     4. Loop over the return values of the _next_ function.  If
  281%        the Python return value unifies with Value, succeed with
  282%        a choicepoint.  Abort on Python or unification exceptions.
  283%     5. Re-satisfaction continues at (4).
  284%
  285%   The example below uses the built-in iterator range():
  286%
  287%       ?- py_iter(range(1,3), X).
  288%       X = 1 ;
  289%       X = 2.
  290%
  291%   Note that the implementation performs a   _look  ahead_, i.e., after
  292%   successful unification it calls `__next__()`   again. On failure the
  293%   Prolog predicate succeeds deterministically. On   success,  the next
  294%   candidate is stored.
  295%
  296%   Note that a Python _generator_ is   a  Python _iterator_. Therefore,
  297%   given  the  Python  generator   expression    below,   we   can  use
  298%   py_iter(squares(1,5),X) to generate the squares on backtracking.
  299%
  300%   ```
  301%   def squares(start, stop):
  302%        for i in range(start, stop):
  303%            yield i * i
  304%   ```
  305%
  306%   @arg Options is processed as with py_call/3.
  307%   @bug Iterator may not depend on janus.query(), i.e., it is not
  308%   possible to iterate over a Python iterator that under the hoods
  309%   relies on a Prolog non-deterministic predicate.
  310%   @compat PIP.  The same remarks as for py_call/2 apply.
  311
  312%!  py_setattr(+Target, +Name, +Value) is det.
  313%
  314%   Set a Python attribute on an object.  If   Target  is an atom, it is
  315%   interpreted  as  a  module.  Otherwise  it  is  normally  an  object
  316%   reference. py_setattr/3 allows for  _chaining_   and  behaves  as if
  317%   defined as
  318%
  319%       py_setattr(Target, Name, Value) :-
  320%           py_call(Target, Obj, [py_object(true)]),
  321%           py_call(setattr(Obj, Name, Value)).
  322%
  323%   @compat PIP
  324
  325%!  py_run(+String, +Globals, +Locals, -Result, +Options) is det.
  326%
  327%   Interface  to  Py_CompileString()  followed   by  PyEval_EvalCode().
  328%   Options:
  329%
  330%       - file_name(String)
  331%         Errors are reported against this pseudo file name
  332%       - start(Token)
  333%         One of `eval`, `file` (default) or `single`.
  334%
  335%   @arg Globals is a dict
  336%   @arg Locals is a dict
  337
  338%!  py_is_object(@Term) is semidet.
  339%
  340%   True when Term is a Python object reference. Fails silently if Term
  341%   is any other Prolog term.
  342%
  343%   @error existence_error(py_object, Term) is raised of Term is a
  344%   Python object, but it has been freed using py_free/1.
  345%
  346%   @compat PIP. The SWI-Prolog implementation is safe in the sense that
  347%   an arbitrary term cannot be confused  with   a  Python  object and a
  348%   reliable error is generated  if  the   references  has  been  freed.
  349%   Portable applications can not rely on this.
  350
  351%!  py_is_dict(@Term) is semidet.
  352%
  353%   True if Term is a Prolog term that represents a Python dict.
  354%
  355%   @compat PIP. The SWI-Prolog version accepts   both a SWI-Prolog dict
  356%   and the `{k:v,...}`  representation.  See   `py_dict_as`  option  of
  357%   py_call/2.
  358
  359py_is_dict(Dict), is_dict(Dict) => true.
  360py_is_dict(py({})) => true.
  361py_is_dict(py({KV})) => is_kv(KV).
  362py_is_dict({KV}) => is_kv(KV).
  363
  364is_kv((K:V,T)) => ground(K), ground(V), is_kv(T).
  365is_kv(K:V) => ground(K), ground(V).
  366
  367
  368%!  py_free(+Obj) is det.
  369%
  370%   Immediately free (decrement the  reference   count)  for  the Python
  371%   object Obj. Further reference  to  Obj   using  e.g.,  py_call/2  or
  372%   py_free/1 raises an `existence_error`. Note that by decrementing the
  373%   reference count, we make the reference invalid from Prolog. This may
  374%   not  actually  delete  the  object  because   the  object  may  have
  375%   references inside Python.
  376%
  377%   Prolog references to Python objects  are   subject  to  atom garbage
  378%   collection and thus normally do not need to be freed explicitly.
  379%
  380%   @compat PIP. The SWI-Prolog  implementation   is  safe  and normally
  381%   reclaiming Python object can  be  left   to  the  garbage collector.
  382%   Portable applications may not assume   garbage  collection of Python
  383%   objects and must ensure to call py_free/1 exactly once on any Python
  384%   object reference. Not calling  py_free/1   leaks  the Python object.
  385%   Calling it twice may lead to undefined behavior.
  386
  387%!  py_with_gil(:Goal) is semidet.
  388%
  389%   Run Goal as  once(Goal)  while  holding   the  Phyton  GIL  (_Global
  390%   Interpreter Lock_). Note that  all   predicates  that  interact with
  391%   Python lock the GIL. This predicate is   only required if we wish to
  392%   make multiple calls to Python while keeping   the  GIL. The GIL is a
  393%   _recursive_ lock and thus calling py_call/1,2  while holding the GIL
  394%   does not _deadlock_.
  395
  396%!  py_gil_owner(-Thread) is semidet.
  397%
  398%   True when  the Python GIL is  owned by Thread.  Note  that, unless
  399%   Thread  is the  calling thread,  this merely  samples the  current
  400%   state and may thus no longer  be true when the predicate succeeds.
  401%   This predicate is intended to help diagnose _deadlock_ problems.
  402%
  403%   Note that  this predicate returns  the Prolog threads  that locked
  404%   the GIL.  It is however possible that Python releases the GIL, for
  405%   example if  it performs a  blocking call.  In this  scenario, some
  406%   other thread or no thread may hold the gil.
  407
  408
  409		 /*******************************
  410		 *         COMPATIBILIY		*
  411		 *******************************/
  412
  413%!  py_func(+Module, +Function, -Return) is det.
  414%!  py_func(+Module, +Function, -Return, +Options) is det.
  415%
  416%   Call Python Function in  Module.   The  SWI-Prolog implementation is
  417%   equivalent to py_call(Module:Function, Return).   See  py_call/2 for
  418%   details.
  419%
  420%   @compat  PIP.  See  py_call/2  for  notes.    Note   that,  as  this
  421%   implementation is based on py_call/2,   Function can use _chaining_,
  422%   e.g., py_func(sys, path:append(dir), Return)  is   accepted  by this
  423%   implementation, but not portable.
  424
  425py_func(Module, Function, Return) :-
  426    py_call(Module:Function, Return).
  427py_func(Module, Function, Return, Options) :-
  428    py_call(Module:Function, Return, Options).
  429
  430%!  py_dot(+Module, +ObjRef, +MethAttr, -Ret) is det.
  431%!  py_dot(+Module, +ObjRef, +MethAttr, -Ret, +Options) is det.
  432%
  433%   Call a method or access  an  attribute   on  the  object ObjRef. The
  434%   SWI-Prolog implementation is equivalent  to py_call(ObjRef:MethAttr,
  435%   Return). See py_call/2 for details.
  436%
  437%   @arg Module is ignored (why do we need that if we have ObjRef?)
  438%   @compat PIP.  See py_func/3 for details.
  439
  440py_dot(_Module, ObjRef, MethAttr, Ret) :-
  441    py_call(ObjRef:MethAttr, Ret).
  442py_dot(_Module, ObjRef, MethAttr, Ret, Options) :-
  443    py_call(ObjRef:MethAttr, Ret, Options).
  444
  445
  446		 /*******************************
  447		 *   PORTABLE ACCESS TO DICTS	*
  448		 *******************************/
  449
  450%!  values(+Dict, +Path, ?Val) is semidet.
  451%
  452%   Get the value associated with Dict at  Path. Path is either a single
  453%   key or a list of keys.
  454%
  455%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  456%   {k:v, ...} term as well as py({k:v, ...}.
  457
  458values(Dict, Key, Val), is_dict(Dict), atom(Key) =>
  459    get_dict(Key, Dict, Val).
  460values(Dict, Keys, Val), is_dict(Dict), is_list(Keys) =>
  461    get_dict_path(Keys, Dict, Val).
  462values(py({CommaDict}), Key, Val) =>
  463    comma_values(CommaDict, Key, Val).
  464values({CommaDict}, Key, Val) =>
  465    comma_values(CommaDict, Key, Val).
  466
  467get_dict_path([], Val, Val).
  468get_dict_path([H|T], Dict, Val) :-
  469    get_dict(H, Dict, Val0),
  470    get_dict_path(T, Val0, Val).
  471
  472comma_values(CommaDict, Key, Val), atom(Key) =>
  473    comma_value(Key, CommaDict, Val).
  474comma_values(CommaDict, Keys, Val), is_list(Keys) =>
  475    comma_value_path(Keys, CommaDict, Val).
  476
  477comma_value(Key, Key:Val0, Val) =>
  478    Val = Val0.
  479comma_value(Key, (_,Tail), Val) =>
  480    comma_value(Key, Tail, Val).
  481
  482comma_value_path([], Val, Val).
  483comma_value_path([H|T], Dict, Val) :-
  484    comma_value(H, Dict, Val0),
  485    comma_value_path(T, Val0, Val).
  486
  487%!  keys(+Dict, ?Keys) is det.
  488%
  489%   True when Keys is a list of keys that appear in Dict.
  490%
  491%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  492%   {k:v, ...} term as well as py({k:v, ...}.
  493
  494keys(Dict, Keys), is_dict(Dict) =>
  495    dict_keys(Dict, Keys).
  496keys(py({CommaDict}), Keys) =>
  497    comma_dict_keys(CommaDict, Keys).
  498keys({CommaDict}, Keys) =>
  499    comma_dict_keys(CommaDict, Keys).
  500
  501comma_dict_keys((Key:_,T), Keys) =>
  502    Keys = [Key|KT],
  503    comma_dict_keys(T, KT).
  504comma_dict_keys(Key:_, Keys) =>
  505    Keys = [Key].
  506
  507%!  key(+Dict, ?Key) is nondet.
  508%
  509%   True when Key is a key in   Dict.  Backtracking enumerates all known
  510%   keys.
  511%
  512%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  513%   {k:v, ...} term as well as py({k:v, ...}.
  514
  515key(Dict, Key), is_dict(Dict) =>
  516    dict_pairs(Dict, _Tag, Pairs),
  517    member(Key-_, Pairs).
  518key(py({CommaDict}), Keys) =>
  519    comma_dict_key(CommaDict, Keys).
  520key({CommaDict}, Keys) =>
  521    comma_dict_key(CommaDict, Keys).
  522
  523comma_dict_key((Key:_,_), Key).
  524comma_dict_key((_,T), Key) :-
  525    comma_dict_key(T, Key).
  526
  527%!  items(+Dict, ?Items) is det.
  528%
  529%   True when Items is a list of Key:Value that appear in Dict.
  530%
  531%   @compat PIP. Note that this predicate   handle  a SWI-Prolog dict, a
  532%   {k:v, ...} term as well as py({k:v, ...}.
  533
  534items(Dict, Items), is_dict(Dict) =>
  535    dict_pairs(Dict, _, Pairs),
  536    maplist(pair_item, Pairs, Items).
  537items(py({CommaDict}), Keys) =>
  538    comma_dict_items(CommaDict, Keys).
  539items({CommaDict}, Keys) =>
  540    comma_dict_items(CommaDict, Keys).
  541
  542pair_item(K-V, K:V).
  543
  544comma_dict_items((Key:Value,T), Keys) =>
  545    Keys = [Key:Value|KT],
  546    comma_dict_items(T, KT).
  547comma_dict_items(Key:Value, Keys) =>
  548    Keys = [Key:Value].
  549
  550
  551		 /*******************************
  552		 *             SHELL		*
  553		 *******************************/
  554
  555%!  py_shell
  556%
  557%   Start an interactive Python REPL  loop   using  the  embedded Python
  558%   interpreter. The interpreter first imports `janus` as below.
  559%
  560%       from janus import *
  561%
  562%   So, we can do
  563%
  564%       ?- py_shell.
  565%       ...
  566%       >>> query_once("writeln(X)", {"X":"Hello world"})
  567%       Hello world
  568%       {'truth': True}
  569%
  570%   If possible, we enable command line   editing using the GNU readline
  571%   library.
  572%
  573%   When used in an environment  where  Prolog   does  not  use the file
  574%   handles 0,1,2 for  the  standard   streams,  e.g.,  in  `swipl-win`,
  575%   Python's I/O is rebound to use  Prolog's I/O. This includes Prolog's
  576%   command line editor, resulting in  a   mixed  history  of Prolog and
  577%   Pythin commands.
  578
  579py_shell :-
  580    import_janus,
  581    py_call(janus_swi:interact(), _).
  582
  583import_janus :-
  584    py_call(sys:hexversion, V),
  585    V >= 0x030A0000,                    % >= 3.10
  586    !,
  587    py_run("from janus_swi import *", py{}, py{}, _, []).
  588import_janus :-
  589    print_message(warning, janus(py_shell(no_janus))).
  590
  591
  592		 /*******************************
  593		 *          UTILITIES           *
  594		 *******************************/
  595
  596%!  py_pp(+Term) is det.
  597%!  py_pp(+Term, +Options) is det.
  598%!  py_pp(+Stream, +Term, +Options) is det.
  599%
  600%   Pretty prints the Prolog translation of a Python data structure in
  601%   Python  syntax. This  exploits  pformat() from  the Python  module
  602%   `pprint` to do the actual  formatting.  Options is translated into
  603%   keyword arguments  passed to  pprint.pformat().  In  addition, the
  604%   option  nl(Bool)  is processed.   When  `true`  (default), we  use
  605%   pprint.pp(), which  makes the output  followed by a  newline.  For
  606%   example:
  607%
  608%   ```
  609%   ?- py_pp(py{a:1, l:[1,2,3], size:1000000},
  610%            [underscore_numbers(true)]).
  611%   {'a': 1, 'l': [1, 2, 3], 'size': 1_000_000}
  612%   ```
  613%
  614%   @compat PIP
  615
  616py_pp(Term) :-
  617    py_pp(current_output, Term, []).
  618
  619py_pp(Term, Options) :-
  620    py_pp(current_output, Term, Options).
  621
  622py_pp(Stream, Term, Options) :-
  623    select_option(nl(NL), Options, Options1, true),
  624    (   NL == true
  625    ->  Method = pp
  626    ;   Method = pformat
  627    ),
  628    opts_kws(Options1, Kws),
  629    PFormat =.. [Method, Term|Kws],
  630    py_call(pprint:PFormat, String),
  631    write(Stream, String).
  632
  633opts_kws(Options, Kws) :-
  634    dict_options(Dict, Options),
  635    dict_pairs(Dict, _, Pairs),
  636    maplist(pair_kws, Pairs, Kws).
  637
  638pair_kws(Name-Value, Name=Value).
  639
  640
  641%!  py_object_dir(+ObjRef, -List) is det.
  642%!  py_object_dict(+ObjRef, -Dict) is det.
  643%
  644%   Examine attributes of  an  object.   The  predicate  py_object_dir/2
  645%   fetches the names of all attributes,   while  py_object_dir/2 gets a
  646%   dict with all attributes and their values.
  647%
  648%   @compat PIP
  649
  650py_object_dir(ObjRef, List) :-
  651    py_call(ObjRef:'__dir__'(), List).
  652
  653py_object_dict(ObjRef, Dict) :-
  654    py_call(ObjRef:'__dict__', Dict).
  655
  656%!  py_obj_dir(+ObjRef, -List) is det.
  657%!  py_obj_dict(+ObjRef, -Dict) is det.
  658%
  659%   @deprecated Use py_object_dir/2 or py_object_dict/2.
  660
  661py_obj_dir(ObjRef, List) :-
  662    py_object_dir(ObjRef, List).
  663
  664py_obj_dict(ObjRef, Dict) :-
  665    py_object_dict(ObjRef, Dict).
  666
  667
  668%!  py_type(+ObjRef, -Type:atom) is det.
  669%
  670%   True when Type is the name of the   type of ObjRef. This is the same
  671%   as ``type(ObjRef).__name__`` in Python.
  672%
  673%   @compat PIP
  674
  675py_type(ObjRef, Type) :-
  676    py_call(type(ObjRef):'__name__', Type).
  677
  678%!  py_isinstance(+ObjRef, +Type) is semidet.
  679%
  680%   True if ObjRef is an instance of Type   or an instance of one of the
  681%   sub types of Type. This  is   the  same as ``isinstance(ObjRef)`` in
  682%   Python.
  683%
  684%   @arg Type is either a term `Module:Type` or a plain atom to refer to
  685%   a built-in type.
  686%
  687%   @compat PIP
  688
  689py_isinstance(Obj, Module:Type) =>
  690    py_call(isinstance(Obj, eval(Module:Type)), @true).
  691py_isinstance(Obj, Type) =>
  692    py_call(isinstance(Obj, eval(sys:modules:'__getitem__'(builtins):Type)), @true).
  693
  694%!  py_module_exists(+Module) is semidet.
  695%
  696%   True if Module is a currently  loaded   Python  module  or it can be
  697%   loaded.
  698%
  699%   @compat PIP
  700
  701py_module_exists(Module) :-
  702    must_be(atom, Module),
  703    py_call(sys:modules:'__contains__'(Module), @true),
  704    !.
  705py_module_exists(Module) :-
  706    py_call(importlib:util:find_spec(Module), R),
  707    R \== @none,
  708    py_free(R).
  709
  710%!  py_hasattr(+ModuleOrObj, ?Name) is nondet.
  711%
  712%   True when Name is an attribute of   Module. The name is derived from
  713%   the Python built-in hasattr(). If Name   is unbound, this enumerates
  714%   the members of py_object_dir/2.
  715%
  716%   @arg ModuleOrObj If this is an atom it refers to a module, otherwise
  717%   it must be a Python object reference.
  718%
  719%   @compat PIP
  720
  721py_hasattr(ModuleOrObj, Name) :-
  722    var(Name),
  723    !,
  724    py_object_dir(ModuleOrObj, Names),
  725    member(Name, Names).
  726py_hasattr(ModuleOrObj, Name) :-
  727    must_be(atom, Name),
  728    (   atom(ModuleOrObj)
  729    ->  py_call(ModuleOrObj:'__name__'), % force loading
  730        py_call(hasattr(eval(sys:modules:'__getitem__'(ModuleOrObj)), Name), @true)
  731    ;   py_call(hasattr(ModuleOrObj, Name), @true)
  732    ).
  733
  734
  735%!  py_module(+Module:atom, +Source:string) is det.
  736%
  737%   Load Source into the Python module Module.   This  is intended to be
  738%   used together with the `string` _quasi quotation_ that supports long
  739%   strings in SWI-Prolog.   For example:
  740%
  741%   ```
  742%   :- use_module(library(strings)).
  743%   :- py_module(hello,
  744%                {|string||
  745%                 | def say_hello_to(s):
  746%                 |     print(f"hello {s}")
  747%                 |}).
  748%   ```
  749%
  750%   Calling this predicate multiple  times  with   the  same  Module and
  751%   Source is a no-op. Called with  a   different  source  creates a new
  752%   Python module that replaces the old in the global namespace.
  753%
  754%   @error python_error(Type, Data) is raised if Python raises an error.
  755
  756:- dynamic py_dyn_module/2 as volatile.  757
  758py_module(Module, Source) :-
  759    variant_sha1(Source, Hash),
  760    (   py_dyn_module(Module, Hash)
  761    ->  true
  762    ;   py_call(janus:import_module_from_string(Module, Source)),
  763        (   retract(py_dyn_module(Module, _))
  764        ->  py_update_module_cache(Module)
  765        ;   true
  766        ),
  767        asserta(py_dyn_module(Module, Hash))
  768    ).
  769
  770
  771		 /*******************************
  772		 *            INIT		*
  773		 *******************************/
  774
  775:- dynamic py_venv/2 as volatile.  776:- dynamic py_is_initialized/0 as volatile.  777
  778%   py_initialize is det.
  779%
  780%   Used as a callback from C for lazy initialization of Python.
  781
  782py_initialize :-
  783    getenv('VIRTUAL_ENV', VEnv),
  784    prolog_to_os_filename(VEnvDir, VEnv),
  785    atom_concat(VEnvDir, '/pyvenv.cfg', Cfg),
  786    access_file(Cfg, read),
  787    !,
  788    current_prolog_flag(executable, Program),
  789    current_prolog_flag(py_argv, Argv),
  790    py_initialize(Program, ['-I'|Argv], []),
  791    py_call(sys:prefix = VEnv),
  792    venv_update_path(VEnvDir).
  793py_initialize :-
  794    current_prolog_flag(executable, Program),
  795    current_prolog_flag(py_argv, Argv),
  796    py_initialize(Program, Argv, []).
  797
  798venv_update_path(VEnvDir) :-
  799    py_call(sys:version_info, Info),    % Tuple
  800    Info =.. [_,Major,Minor|_],
  801    format(string(EnvSiteDir),
  802           '~w/lib/python~w.~w/site-packages',
  803           [VEnvDir, Major, Minor]),
  804    prolog_to_os_filename(EnvSiteDir, PyEnvSiteDir),
  805    (   exists_directory(EnvSiteDir)
  806    ->  true
  807    ;   print_message(warning,
  808                      janus(venv(no_site_package_dir(VEnvDir, EnvSiteDir))))
  809    ),
  810    py_call(sys:path, Path0),
  811    exclude(is_site_dir, Path0, Path1),
  812    append(Path1, [PyEnvSiteDir], Path),
  813    py_call(sys:path = Path),
  814    print_message(silent, janus(venv(VEnvDir, EnvSiteDir))),
  815    asserta(py_venv(VEnvDir, EnvSiteDir)).
  816
  817is_site_dir(OsDir) :-
  818    prolog_to_os_filename(PlDir, OsDir),
  819    file_base_name(PlDir, Dir0),
  820    downcase_atom(Dir0, Dir),
  821    no_env_dir(Dir).
  822
  823no_env_dir('site-packages').
  824no_env_dir('dist-packages').
  825
  826%!  py_initialize(+Program, +Argv, +Options) is det.
  827%
  828%   Initialize  and configure  the  embedded Python  system.  If  this
  829%   predicate is  not called before any  other call to Python  such as
  830%   py_call/2, it is called _lazily_, passing the Prolog executable as
  831%   Program, passing Argv from the  Prolog flag `py_argv` and an empty
  832%   Options list.
  833%
  834%   Calling this predicate while the  Python is already initialized is
  835%   a  no-op.  This  predicate is  thread-safe, where  the first  call
  836%   initializes Python.
  837%
  838%   In addition to initializing the Python system, it
  839%
  840%     - Adds the directory holding `janus.py` to the Python module
  841%       search path.
  842%     - If Prolog I/O is not connected to the file handles 0,1,2,
  843%       it rebinds Python I/O to use the Prolog I/O.
  844%
  845%   @arg Options is currently ignored.  It will be used to provide
  846%   additional configuration options.
  847
  848py_initialize(Program, Argv, Options) :-
  849    (   py_initialize_(Program, Argv, Options)
  850    ->  absolute_file_name(library('python/janus.py'), Janus,
  851			   [ access(read) ]),
  852	file_directory_name(Janus, PythonDir),
  853	py_add_lib_dir(PythonDir, first),
  854	py_connect_io,
  855        repl_add_cwd,
  856        asserta(py_is_initialized)
  857    ;   true
  858    ).
  859
  860%!  py_connect_io is det.
  861%
  862%   If SWI-Prolog console streams are bound to something non-standard,
  863%   bind the Python console I/O to our streans.
  864
  865py_connect_io :-
  866    maplist(non_file_stream,
  867	    [0-user_input, 1-user_output, 2-user_error],
  868	    NonFiles),
  869    Call =.. [connect_io|NonFiles],
  870    py_call(janus_swi:Call).
  871
  872non_file_stream(Expect-Stream, Bool) :-
  873    (   stream_property(Stream, file_no(Expect))
  874    ->  Bool = @false
  875    ;   Bool = @true
  876    ).
  877
  878		 /*******************************
  879		 *            PATHS		*
  880		 *******************************/
  881
  882%!  py_lib_dirs(-Dirs) is det.
  883%
  884%   True when Dirs is a list of directories searched for Python modules.
  885%   The elements of Dirs are in Prolog canonical notation.
  886%
  887%   @compat PIP
  888
  889py_lib_dirs(Dirs) :-
  890    py_call(sys:path, Dirs0),
  891    maplist(prolog_to_os_filename, Dirs, Dirs0).
  892
  893%!  py_add_lib_dir(+Dir) is det.
  894%!  py_add_lib_dir(+Dir, +Where) is det.
  895%
  896%   Add a directory to the Python  module   search  path.  In the second
  897%   form, Where is one of `first`   or `last`. py_add_lib_dir/1 adds the
  898%   directory as `last`. The property `sys:path`   is not modified if it
  899%   already contains Dir.
  900%
  901%   Dir is in Prolog notation. The added   directory  is converted to an
  902%   absolute path using the OS notation using prolog_to_os_filename/2.
  903%
  904%   If Dir is a _relative_ path, it   is taken relative to Prolog source
  905%   file when used as a _directive_ and  relative to the process working
  906%   directory when called as a predicate.
  907%
  908%   @compat PIP. Note  that  SWI-Prolog   uses  POSIX  file  conventions
  909%   internally, mapping to OS  conventions   inside  the predicates that
  910%   deal with files or explicitly   using prolog_to_os_filename/2. Other
  911%   systems may use the native file conventions in Prolog.
  912
  913:- multifile system:term_expansion/2.  914
  915system:term_expansion((:- py_add_lib_dir(Dir0)),
  916                      (:- initialization(py_add_lib_dir(Dir, first), now))) :-
  917    \+ is_absolute_file_name(Dir0),
  918    prolog_load_context(directory, CWD),
  919    absolute_file_name(Dir0, Dir, [relative_to(CWD)]).
  920system:term_expansion((:- py_add_lib_dir(Dir0, Where)),
  921                      (:- initialization(py_add_lib_dir(Dir, Where), now))) :-
  922    \+ is_absolute_file_name(Dir0),
  923    prolog_load_context(directory, CWD),
  924    absolute_file_name(Dir0, Dir, [relative_to(CWD)]),
  925    absolute_file_name(Dir0, Dir).
  926
  927py_add_lib_dir(Dir) :-
  928    py_add_lib_dir(Dir, last).
  929
  930py_add_lib_dir(Dir, Where) :-
  931    absolute_file_name(Dir, AbsDir),
  932    prolog_to_os_filename(AbsDir, OSDir),
  933    py_add_lib_dir_(OSDir, Where).
  934
  935py_add_lib_dir_(OSDir, Where) :-
  936    (   py_call(sys:path, Dirs0),
  937        memberchk(OSDir, Dirs0)
  938    ->  true
  939    ;   Where == last
  940    ->  py_call(sys:path:append(OSDir), _)
  941    ;   Where == first
  942    ->  py_call(sys:path:insert(0, OSDir), _)
  943    ;   must_be(oneof([first,last]), Where)
  944    ).
  945
  946repl_add_cwd :-
  947    current_prolog_flag(break_level, Level),
  948    Level >= 0,
  949    (   py_call(sys:path:count(''), N),
  950        N > 0
  951    ->  true
  952    ;   print_message(informational, janus(add_cwd)),
  953        py_add_lib_dir_('', first)
  954    ).
  955
  956:- multifile
  957    prolog:repl_loop_hook/2.  958
  959prolog:repl_loop_hook(begin, Level) :-
  960    Level >= 0,
  961    py_is_initialized,
  962    repl_add_cwd.
  963
  964
  965		 /*******************************
  966		 *           CALLBACK		*
  967		 *******************************/
  968
  969:- dynamic py_call_cache/8 as volatile.  970
  971:- meta_predicate py_call_string(:, +, -).  972
  973%   py_call_string(:String, +DictIn, -Dict) is nondet.
  974%
  975%   Support janus.query_once() and janus.query(). Parses   String  into a goal
  976%   term. Next, all variables from the goal   term that appear in DictIn
  977%   are bound to the value from  this   dict.  Dict  is created from the
  978%   remaining variables, unless they  start   with  an underscore (e.g.,
  979%   `_Time`) and the key `truth. On   success,  the Dict values contain
  980%   the bindings from the  answer  and   `truth`  is  either  `true` or
  981%   `Undefined`. On failure, the Dict values are bound to `None` and the
  982%   `truth` is `false`.
  983%
  984%   Parsing and distributing the variables over the two dicts is cached.
  985
  986py_call_string(M:String, Input, Dict) :-
  987    py_call_cache(String, Input, TV, M, Goal, Dict, Truth, OutVars),
  988    !,
  989    py_call(TV, M:Goal, Truth, OutVars).
  990py_call_string(M:String, Input, Dict) :-
  991    term_string(Goal, String, [variable_names(Map)]),
  992    unbind_dict(Input, VInput),
  993    exclude(not_in_projection(VInput), Map, OutBindings),
  994    dict_create(Dict, bindings, [truth=Truth|OutBindings]),
  995    maplist(arg(2), OutBindings, OutVars),
  996    TV = Input.get(truth, 'PLAIN_TRUTHVALS'),
  997    asserta(py_call_cache(String, VInput, TV, M, Goal, Dict, Truth, OutVars)),
  998    VInput = Input,
  999    py_call(TV, M:Goal, Truth, OutVars).
 1000
 1001py_call('NO_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1002    (   call(M:Goal)
 1003    *-> bind_status_no_no_truthvals(Truth)
 1004    ;   Truth = @false,
 1005	maplist(bind_none, OutVars)
 1006    ).
 1007py_call('PLAIN_TRUTHVALS', M:Goal, Truth, OutVars) =>
 1008    (   call(M:Goal)
 1009    *-> bind_status_plain_truthvals(Truth)
 1010    ;   Truth = @false,
 1011	maplist(bind_none, OutVars)
 1012    ).
 1013py_call('DELAY_LISTS', M:Goal, Truth, OutVars) =>
 1014    (   call_delays(M:Goal, Delays)
 1015    *-> bind_status_delay_lists(Delays, Truth)
 1016    ;   Truth = @false,
 1017	maplist(bind_none, OutVars)
 1018    ).
 1019py_call('RESIDUAL_PROGRAM', M:Goal, Truth, OutVars) =>
 1020    (   call_delays(M:Goal, Delays)
 1021    *-> bind_status_residual_program(Delays, Truth)
 1022    ;   Truth = @false,
 1023	maplist(bind_none, OutVars)
 1024    ).
 1025
 1026not_in_projection(Input, Name=Value) :-
 1027    (   get_dict(Name, Input, Value)
 1028    ->  true
 1029    ;   sub_atom(Name, 0, _, _, '_')
 1030    ).
 1031
 1032bind_none(@none).
 1033
 1034bind_status_no_no_truthvals(@true).
 1035
 1036bind_status_plain_truthvals(Truth) =>
 1037    (   '$tbl_delay_list'([])
 1038    ->  Truth = @true
 1039    ;   py_undefined(Truth)
 1040    ).
 1041
 1042bind_status_delay_lists(true, Truth) =>
 1043    Truth = @true.
 1044bind_status_delay_lists(Delays, Truth) =>
 1045    py_call(janus:'Undefined'(prolog(Delays)), Truth).
 1046
 1047bind_status_residual_program(true, Truth) =>
 1048    Truth = @true.
 1049bind_status_residual_program(Delays, Truth) =>
 1050    delays_residual_program(Delays, Program),
 1051    py_call(janus:'Undefined'(prolog(Program)), Truth).
 1052
 1053py_undefined(X) :-
 1054    py_call(janus:undefined, X).
 1055
 1056unbind_dict(Dict0, Dict) :-
 1057    dict_pairs(Dict0, Tag, Pairs0),
 1058    maplist(unbind, Pairs0, Pairs),
 1059    dict_pairs(Dict, Tag, Pairs).
 1060
 1061unbind(Name-_, Name-_) :-
 1062    sub_atom(Name, 0, 1, _, Char1),
 1063    char_type(Char1, prolog_var_start),
 1064    !.
 1065unbind(NonVar, NonVar).
 1066
 1067
 1068		 /*******************************
 1069		 *     SUPPORT PYTHON CALLS     *
 1070		 *******************************/
 1071
 1072:- public
 1073       px_cmd/3,
 1074       px_call/4,
 1075       px_comp/7. 1076
 1077% These predicates are helpers  for the corresponding Python functions
 1078% in janus.py.
 1079
 1080
 1081%   px_call(+Input:tuple, +Module, -Pred, -Ret)
 1082%
 1083%   Supports  px_qdet()  and  apply().  Note    that   these  predicates
 1084%   explicitly address predicates  in  a   particular  module.  For meta
 1085%   predicates, this implies they also control  the context module. This
 1086%   leads to ``janus.cmd("consult", "consult", file)`` to consult _file_
 1087%   into the module `consult`, which is not   what we want. Therefore we
 1088%   set the context module to `user`, which is better, but probably also
 1089%   not what we want.
 1090
 1091px_call(-(), Module, Pred, Ret) =>
 1092    @(call(Module:Pred, Ret), user).
 1093px_call(-(A1), Module, Pred, Ret) =>
 1094    @(call(Module:Pred, A1, Ret), user).
 1095px_call(-(A1,A2), Module, Pred, Ret) =>
 1096    @(call(Module:Pred, A1, A2, Ret), user).
 1097px_call(-(A1,A2,A3), Module, Pred, Ret) =>
 1098    @(call(Module:Pred, A1, A2, A3, Ret), user).
 1099px_call(-(A1,A2,A3,A4), Module, Pred, Ret) =>
 1100    @(call(Module:Pred, A1, A2, A3, A4, Ret), user).
 1101px_call(Tuple, Module, Pred, Ret) =>
 1102    compound_name_arguments(Tuple, _, Args),
 1103    append(Args, [Ret], GArgs),
 1104    Goal =.. [Pred|GArgs],
 1105    @(Module:Goal, user).
 1106
 1107px_cmd(Module, Pred, Tuple) :-
 1108    (   compound(Tuple)
 1109    ->  compound_name_arguments(Tuple, _, Args),
 1110	Goal =.. [Pred|Args]
 1111    ;   Goal = Pred
 1112    ),
 1113    @(Module:Goal, user).
 1114
 1115px_comp(Module, Pred, Tuple, Vars, Set, TV, Ret) :-
 1116    length(Out, Vars),
 1117    (   compound(Tuple)
 1118    ->  compound_name_arguments(Tuple, _, Args),
 1119	append(Args, Out, GArgs),
 1120	Goal =.. [Pred|GArgs]
 1121    ;   Goal =.. [Pred|Out]
 1122    ),
 1123    compound_name_arguments(OTempl0, -, Out),
 1124    tv_goal_and_template(TV, @(Module:Goal, user), FGoal, OTempl0, OTempl),
 1125    findall(OTempl, FGoal, Ret0),
 1126    (   Set == @true
 1127    ->  sort(Ret0, Ret)
 1128    ;   Ret = Ret0
 1129    ).
 1130
 1131:- meta_predicate
 1132    call_delays_py(0, -). 1133
 1134% 0,1,2: TruthVal(Enum) from janus.py
 1135tv_goal_and_template('NO_TRUTHVALS',
 1136                     Goal, Goal, Templ, Templ) :- !.
 1137tv_goal_and_template('PLAIN_TRUTHVALS',
 1138                     Goal, ucall(Goal, TV), Templ, -(Templ,TV)) :- !.
 1139tv_goal_and_template('DELAY_LISTS',
 1140                     Goal, call_delays_py(Goal, TV), Templ, -(Templ,TV)) :- !.
 1141tv_goal_and_template(Mode, _, _, _, _) :-
 1142    domain_error("px_comp() truth", Mode).
 1143
 1144:- public
 1145    ucall/2,
 1146    call_delays_py/2. 1147
 1148ucall(Goal, TV) :-
 1149    call(Goal),
 1150    (   '$tbl_delay_list'([])
 1151    ->  TV = 1
 1152    ;   TV = 2
 1153    ).
 1154
 1155call_delays_py(Goal, PyDelays) :-
 1156    call_delays(Goal, Delays),
 1157    (   Delays == true
 1158    ->  PyDelays = []
 1159    ;   comma_list(Delays, Array),
 1160        maplist(term_string, Array, PyDelays)
 1161    ).
 1162
 1163
 1164		 /*******************************
 1165		 *          PYTHON I/O          *
 1166		 *******************************/
 1167
 1168%   py_write(+Stream, -String) is det.
 1169%   py_readline(+Stream, +Size, +Prompt, +Line) is det.
 1170%
 1171%   Called from redefined Python console  I/O   to  write/read using the
 1172%   Prolog streams.
 1173
 1174:- '$hide'((py_write/1,
 1175	    py_readline/4)). 1176
 1177py_write(Stream, String) :-
 1178    notrace(format(Stream, '~s', [String])).
 1179
 1180py_readline(Stream, Size, Prompt, Line) :-
 1181    notrace(py_readline_(Stream, Size, Prompt, Line)).
 1182
 1183py_readline_(Stream, _Size, Prompt, Line) :-
 1184    prompt1(Prompt),
 1185    read_line_to_string(Stream, Read),
 1186    (   Read == end_of_file
 1187    ->  Line = ""
 1188    ;   string_concat(Read, "\n", Line),
 1189	py_add_history(Read)
 1190    ).
 1191
 1192py_add_history(Line) :-
 1193    ignore(catch(prolog:history(user_input, add(Line)), _, true)).
 1194
 1195
 1196		 /*******************************
 1197		 *          COMPILING           *
 1198		 *******************************/
 1199
 1200%   py_consult(+File, +Data, +Module) is det.
 1201%
 1202%   Support janus.consult(file, data=None, module='user').
 1203
 1204:- public py_consult/3. 1205py_consult(File, @none, Module) =>
 1206    consult(Module:File).
 1207py_consult(File, Data, Module) =>
 1208    setup_call_cleanup(
 1209	open_string(Data, In),
 1210	load_files(Module:File, [stream(In)]),
 1211	close(In)).
 1212
 1213
 1214		 /*******************************
 1215		 *           MESSAGES		*
 1216		 *******************************/
 1217
 1218:- multifile
 1219    prolog:error_message//1,
 1220    prolog:message_context//1,
 1221    prolog:message//1. 1222
 1223prolog:error_message(python_error(Class, Value)) -->
 1224    { py_str(Value, Message)
 1225    },
 1226    [ 'Python ', ansi(code, "'~w'", [Class]), ':', nl,
 1227      '  ~w'-[Message]
 1228    ].
 1229
 1230prolog:message_context(context(_, PythonCtx)) -->
 1231    { nonvar(PythonCtx),
 1232      PythonCtx = python_stack(Stack),
 1233      current_prolog_flag(py_backtrace, true),
 1234      py_is_object(Stack),
 1235      !,
 1236      current_prolog_flag(py_backtrace_depth, Depth),
 1237      py_call(traceback:format_tb(Stack, Depth), Frames)
 1238    },
 1239    [ nl, 'Python stack:', nl ],
 1240    sequence(py_stack_frame, Frames).
 1241
 1242py_stack_frame(String) -->
 1243    { split_string(String, "\n", "", Lines)
 1244    },
 1245    sequence(msg_line, [nl], Lines).
 1246
 1247msg_line(Line) -->
 1248    [ '~s'-[Line] ].
 1249
 1250prolog:message(janus(Msg)) -->
 1251    message(Msg).
 1252
 1253message(version(Janus, Python)) -->
 1254    [ 'Janus ~w embeds Python ~w'-[Janus, Python] ].
 1255message(venv(Dir, _EnvSiteDir)) -->
 1256    [ 'Janus: using venv from ~p'-[Dir] ].
 1257message(venv(no_site_package_dir(VEnvDir, Dir))) -->
 1258    [ 'Janus: venv dirrectory ~p does not contain ~p'-[VEnvDir, Dir] ].
 1259message(py_shell(no_janus)) -->
 1260    [ 'Janus: py_shell/0: Importing janus into the Python shell requires Python 3.10 or later.', nl,
 1261      'Run "', ansi(code, 'from janus import *', []), '" in the Python shell to import janus.'
 1262    ].
 1263message(add_cwd) -->
 1264    [ 'Interactive session; added `.` to Python `sys.path`'-[] ]