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_obj_dir/2, % +ObjRef,-List 67 py_obj_dict/2, % obj_dict(+ObjRef, -Dict) 68 69 py_module/2, % +Module:atom, +Source:string 70 71 py_initialize/3, % +Program, +Argv, +Options 72 py_lib_dirs/1, % -Dirs 73 py_add_lib_dir/1, % +Dir 74 py_add_lib_dir/2, % +Dir,+Where 75 76 op(200, fy, @), % @constant 77 op(50, fx, #) % #Value 78 ]). 79:- meta_predicate py_with_gil( ). 80 81:- use_module(library(apply_macros), []). 82:- autoload(library(lists), [append/3, member/2]). 83:- autoload(library(apply), [maplist/2, exclude/3, maplist/3]). 84:- autoload(library(error), [must_be/2, domain_error/2]). 85:- autoload(library(dicts), [dict_keys/2]). 86:- autoload(library(option), [dict_options/2]). 87:- autoload(library(prolog_code), [comma_list/2]). 88:- autoload(library(readutil), [read_line_to_string/2]). 89:- autoload(library(wfs), [call_delays/2, delays_residual_program/2]). 90 91:- if(\+current_predicate(py_call/1)). 92:- if(current_prolog_flag(windows, true)). 93:- use_module(library(shlib), [win_add_dll_directory/1]). 94 95% Just having the Python dir in PATH seems insufficient. We also need to 96% add the directory to the DLL search path. 97add_python_dll_dir :- 98 absolute_file_name(path('python3.dll'), DLL, [access(read)]), 99 file_directory_name(DLL, Dir), 100 win_add_dll_directory(Dir). 101:- initialization(add_python_dll_dir, now). 102:- endif. 103 104:- use_foreign_library(foreign(janus), [visibility(global)]). 105:- endif. 106 107:- predicate_options(py_call/3, 3, 108 [ py_object(boolean), 109 py_string_as(oneof([string,atom])) 110 ]). 111:- predicate_options(py_func/4, 4, 112 [ sizecheck(boolean), 113 pass_to(py_call/3, 3) 114 ]). 115:- predicate_options(py_dot/5, 5, 116 [ sizecheck(boolean), 117 pass_to(py_call/3, 3) 118 ]). 119 120:- public 121 py_initialize/0, 122 py_call_string/3, 123 py_write/2, 124 py_readline/4.
sys.version
. If a Python virtual environment (venv) is
active, indicate this with the location of this environment found.
146py_version :-
147 py_call(sys:version, X),
148 print_message(information, janus(version(X))),
149 ( py_venv(VEnvDir, EnvSiteDir)
150 -> print_message(information, janus(venv(VEnvDir, EnvSiteDir)))
151 ; true
152 ).
Arguments to Python functions use the Python conventions. Both
positional and keyword arguments are supported. Keyword
arguments are written as Name = Value
and must appear after the
positional arguments.
Below are some examples.
% call a built-in ?- py_call(print("Hello World!\n")). true. % call a built-in (alternative) ?- py_call(builtins:print("Hello World!\n")). true. % call function in a module ?- py_call(sys:getsizeof([1,2,3]), Size). Size = 80. % call function on an attribute of a module ?- py_call(sys:path:append("/home/bob/janus")). true % get attribute from a module ?- py_call(sys:path, Path) Path = ["dir1", "dir2", ...]
Given a class in a file dog.py
such as the following example from
the Python documentation
class Dog: tricks = [] def __init__(self, name): self.name = name def add_trick(self, trick): self.tricks.append(trick)
We can interact with this class as below. Note that $Doc
in the
SWI-Prolog toplevel refers to the last toplevel binding for the
variable Dog.
?- py_call(dog:'Dog'("Fido"), Dog). Dog = <py_Dog>(0x7f095c9d02e0). ?- py_call($Dog:add_trick("roll_over")). Dog = <py_Dog>(0x7f095c9d02e0). ?- py_call($Dog:tricks, Tricks). Dog = <py_Dog>(0x7f095c9d02e0), Tricks = ["roll_over"]
If the principal term of the first argument is not Target:Func
,
The argument is evaluated as the initial target, i.e., it must be an
object reference or a module. For example:
?- py_call(dog:'Dog'("Fido"), Dog), py_call(Dog, X). Dog = X, X = <py_Dog>(0x7fa8cbd12050). ?- py_call(sys, S). S = <py_module>(0x7fa8cd582390).
Options processed:
true
(default false
), translate the return as a Python
object reference. Some objects are always translated to
Prolog, regardless of this flag. These are the Python constants
None
, True
and False
as well as instances of the
Python base classes int
, float
, str
or tuple
. Instances
of sub classes of these base classes are controlled by this
option.atom
(default), translate a Python String into a
Prolog atom. If Type is string
, translate into a Prolog string.
Strings are more efficient if they are short lived.dict
(default) to map a Python dict to a SWI-Prolog
dict if all keys can be represented. If {}
or not all keys
can be represented, Return is unified to a term {k:v, ...}
or py({})
if the Python dict is empty.Obj:Attr = Value
construct is not accepted.__iter__
on the result to get the iterator itself.__next__
function of the iterator.
The example below uses the built-in iterator range()
:
?- py_iter(range(1,3), X). X = 1 ; X = 2.
Note that the implementation performs a look ahead, i.e., after successful unification it calls `__next__()` again. On failure the Prolog predicate succeeds deterministically. On success, the next candidate is stored.
Note that a Python generator is a Python iterator. Therefore,
given the Python generator expression below, we can use
py_iter(squares(1,5),X)
to generate the squares on backtracking.
def squares(start, stop): for i in range(start, stop): yield i * i
py_setattr(Target, Name, Value) :- py_call(Target, Obj, [py_object(true)]), py_call(setattr(Obj, Name, Value)).
eval
, file
(default) or single
.349py_is_dict(Dict), is_dict(Dict) => true. 350py_is_dict(py({})) => true. 351py_is_dict(py({KV})) => is_kv(KV). 352py_is_dict({KV}) => is_kv(KV). 353 354is_kv((K:V,T)) => ground(K), ground(V), is_kv(T). 355is_kv(K:V) => ground(K), ground(V).
existence_error
. Note that by decrementing the
reference count, we make the reference invalid from Prolog. This may
not actually delete the object because the object may have
references inside Python.
Prolog references to Python objects are subject to atom garbage collection and thus normally do not need to be freed explicitly.
once(Goal)
while holding the Phyton GIL (Global
Interpreter Lock). Note that all predicates that interact with
Python lock the GIL. This predicate is only required if we wish to
make multiple calls to Python while keeping the GIL. The GIL is a
recursive lock and thus calling py_call/1,2 while holding the GIL
does not deadlock.Note that this predicate returns the Prolog threads that locked the GIL. It is however possible that Python releases the GIL, for example if it performs a blocking call. In this scenario, some other thread or no thread may hold the gil.
399 /******************************* 400 * COMPATIBILIY * 401 *******************************/
py_call(Module:Function, Return)
. See py_call/2 for
details.
415py_func(Module, Function, Return) :- 416 py_call(Module:Function, Return). 417py_func(Module, Function, Return, Options) :- 418 py_call(Module:Function, Return, Options).
py_call(ObjRef:MethAttr,
Return)
. See py_call/2 for details.
430py_dot(_Module, ObjRef, MethAttr, Ret) :- 431 py_call(ObjRef:MethAttr, Ret). 432py_dot(_Module, ObjRef, MethAttr, Ret, Options) :- 433 py_call(ObjRef:MethAttr, Ret, Options). 434 435 436 /******************************* 437 * PORTABLE ACCESS TO DICTS * 438 *******************************/
448values(Dict, Key, Val), is_dict(Dict), atom(Key) => 449 get_dict(Key, Dict, Val). 450values(Dict, Keys, Val), is_dict(Dict), is_list(Keys) => 451 get_dict_path(Keys, Dict, Val). 452values(py({CommaDict}), Key, Val) => 453 comma_values(CommaDict, Key, Val). 454values({CommaDict}, Key, Val) => 455 comma_values(CommaDict, Key, Val). 456 457get_dict_path([], Val, Val). 458get_dict_path([H|T], Dict, Val) :- 459 get_dict(H, Dict, Val0), 460 get_dict_path(T, Val0, Val). 461 462comma_values(CommaDict, Key, Val), atom(Key) => 463 comma_value(Key, CommaDict, Val). 464comma_values(CommaDict, Keys, Val), is_list(Keys) => 465 comma_value_path(Keys, CommaDict, Val). 466 467comma_value(Key, Key:Val0, Val) => 468 Val = Val0. 469comma_value(Key, (_,Tail), Val) => 470 comma_value(Key, Tail, Val). 471 472comma_value_path([], Val, Val). 473comma_value_path([H|T], Dict, Val) :- 474 comma_value(H, Dict, Val0), 475 comma_value_path(T, Val0, Val).
484keys(Dict, Keys), is_dict(Dict) => 485 dict_keys(Dict, Keys). 486keys(py({CommaDict}), Keys) => 487 comma_dict_keys(CommaDict, Keys). 488keys({CommaDict}, Keys) => 489 comma_dict_keys(CommaDict, Keys). 490 491comma_dict_keys((Key:_,T), Keys) => 492 Keys = [Key|KT], 493 comma_dict_keys(T, KT). 494comma_dict_keys(Key:_, Keys) => 495 Keys = [Key].
505key(Dict, Key), is_dict(Dict) => 506 dict_pairs(Dict, _Tag, Pairs), 507 member(Key-_, Pairs). 508key(py({CommaDict}), Keys) => 509 comma_dict_key(CommaDict, Keys). 510key({CommaDict}, Keys) => 511 comma_dict_key(CommaDict, Keys). 512 513comma_dict_key((Key:_,_), Key). 514comma_dict_key((_,T), Key) :- 515 comma_dict_key(T, Key).
524items(Dict, Items), is_dict(Dict) => 525 dict_pairs(Dict, _, Pairs), 526 maplist(pair_item, Pairs, Items). 527items(py({CommaDict}), Keys) => 528 comma_dict_items(CommaDict, Keys). 529items({CommaDict}, Keys) => 530 comma_dict_items(CommaDict, Keys). 531 532pair_item(K-V, K:V). 533 534comma_dict_items((Key:Value,T), Keys) => 535 Keys = [Key:Value|KT], 536 comma_dict_items(T, KT). 537comma_dict_items(Key:Value, Keys) => 538 Keys = [Key:Value]. 539 540 541 /******************************* 542 * SHELL * 543 *******************************/
janus
as below.
from janus import *
So, we can do
?- py_shell. ... >>> query_once("writeln(X)", {"X":"Hello world"}) Hello world {'truth': True}
If possible, we enable command line editing using the GNU readline library.
When used in an environment where Prolog does not use the file
handles 0,1,2 for the standard streams, e.g., in swipl-win
,
Python's I/O is rebound to use Prolog's I/O. This includes Prolog's
command line editor, resulting in a mixed history of Prolog and
Pythin commands.
569py_shell :- 570 import_janus, 571 py_call(janus_swi:interact(), _). 572 573import_janus :- 574 py_call(sys:hexversion, V), 575 V >= 0x030A0000, % >= 3.10 576 !, 577 py_run("from janus_swi import *", py{}, py{}, _, []). 578import_janus :- 579 print_message(warning, janus(py_shell(no_janus))). 580 581 582 /******************************* 583 * UTILITIES * 584 *******************************/
pformat()
from the Python module
pprint
to do the actual formatting. Options is translated into
keyword arguments passed to pprint.pformat()
. In addition, the
option nl(Bool)
is processed. When true
(default), we use
pprint.pp()
, which makes the output followed by a newline. For
example:
?- py_pp(py{a:1, l:[1,2,3], size:1000000}, [underscore_numbers(true)]). {'a': 1, 'l': [1, 2, 3], 'size': 1_000_000}
606py_pp(Term) :- 607 py_pp(current_output, Term, []). 608 609py_pp(Term, Options) :- 610 py_pp(current_output, Term, Options). 611 612py_pp(Stream, Term, Options) :- 613 select_option(nl(NL), Options, Options1, true), 614 ( NL == true 615 -> Method = pp 616 ; Method = pformat 617 ), 618 opts_kws(Options1, Kws), 619 PFormat =.. [Method, Term|Kws], 620 py_call(pprint:PFormat, String), 621 write(Stream, String). 622 623opts_kws(Options, Kws) :- 624 dict_options(Dict, Options), 625 dict_pairs(Dict, _, Pairs), 626 maplist(pair_kws, Pairs, Kws). 627 628pair_kws(Name-Value, Name=Value).
640py_obj_dir(ObjRef, List) :- 641 py_call(ObjRef:'__dir__'(), List). 642 643py_obj_dict(ObjRef, Dict) :- 644 py_call(ObjRef:'__dict__', Dict).
string
quasi quotation that supports long
strings in SWI-Prolog. For example:
:- use_module(library(strings)). :- py_module(hello, {|string|| | def say_hello_to(s): | print(f"hello {s}") |}).
Calling this predicate multiple times with the same Module and Source is a no-op. Called with a different source creates a new Python module that replaces the old in the global namespace.
669:- dynamic py_dyn_module/2 as volatile. 670 671py_module(Module, Source) :- 672 variant_sha1(Source, Hash), 673 ( py_dyn_module(Module, Hash) 674 -> true 675 ; py_call(janus:import_module_from_string(Module, Source)), 676 ( retract(py_dyn_module(Module, _)) 677 -> py_update_module_cache(Module) 678 ; true 679 ), 680 asserta(py_dyn_module(Module, Hash)) 681 ). 682 683 684 /******************************* 685 * INIT * 686 *******************************/ 687 688:- dynamic py_venv/2 as volatile. 689 690% py_initialize is det. 691% 692% Used as a callback from C for lazy initialization of Python. 693 694py_initialize :- 695 getenv('VIRTUAL_ENV', VEnv), 696 prolog_to_os_filename(VEnvDir, VEnv), 697 atom_concat(VEnvDir, '/pyvenv.cfg', Cfg), 698 access_file(Cfg, read), 699 !, 700 current_prolog_flag(executable, Program), 701 py_initialize(Program, ['-I'], []), 702 py_call(sys:prefix = VEnv), 703 venv_update_path(VEnvDir). 704py_initialize :- 705 current_prolog_flag(executable, Program), 706 current_prolog_flag(argv, Argv), 707 py_initialize(Program, Argv, []). 708 709venv_update_path(VEnvDir) :- 710 py_call(sys:version_info, Info), % Tuple 711 Info =.. [_,Major,Minor|_], 712 format(string(EnvSiteDir), 713 '~w/lib/python~w.~w/site-packages', 714 [VEnvDir, Major, Minor]), 715 prolog_to_os_filename(EnvSiteDir, PyEnvSiteDir), 716 ( exists_directory(EnvSiteDir) 717 -> true 718 ; print_message(warning, 719 janus(venv(no_site_package_dir(VEnvDir, EnvSiteDir)))) 720 ), 721 py_call(sys:path, Path0), 722 exclude(is_site_dir, Path0, Path1), 723 append(Path1, [PyEnvSiteDir], Path), 724 py_call(sys:path = Path), 725 print_message(silent, janus(venv(VEnvDir, EnvSiteDir))), 726 asserta(py_venv(VEnvDir, EnvSiteDir)). 727 728is_site_dir(OsDir) :- 729 prolog_to_os_filename(PlDir, OsDir), 730 file_base_name(PlDir, Dir0), 731 downcase_atom(Dir0, Dir), 732 no_env_dir(Dir). 733 734no_env_dir('site-packages'). 735no_env_dir('dist-packages').
Calling this predicate while the Python is already initialized is a no-op. This predicate is thread-safe, where the first call initializes Python.
In addition to initializing the Python system, it
janus.py
to the Python module
search path.
759py_initialize(Program, Argv, Options) :-
760 ( py_initialize_(Program, Argv, Options)
761 -> absolute_file_name(library('python/janus.py'), Janus,
762 [ access(read) ]),
763 file_directory_name(Janus, PythonDir),
764 py_add_lib_dir(PythonDir, first),
765 py_connect_io
766 ; true
767 ).
774py_connect_io :- 775 maplist(non_file_stream, 776 [0-user_input, 1-user_output, 2-user_error], 777 NonFiles), 778 Call =.. [connect_io|NonFiles], 779 py_call(janus_swi:Call). 780 781non_file_stream(Expect-Stream, Bool) :- 782 ( stream_property(Stream, file_no(Expect)) 783 -> Bool = @false 784 ; Bool = @true 785 ). 786 787 /******************************* 788 * PATHS * 789 *******************************/
798py_lib_dirs(Dirs) :-
799 py_call(sys:path, Dirs0),
800 maplist(prolog_to_os_filename, Dirs, Dirs0).
first
or last
. py_add_lib_dir/1 adds the
directory as first. The property sys:path
is not modified if it
already contains Dir.
Dir is in Prolog notation. The added directory is converted to an absolute path using the OS notation.
The form py_add_lib_dir/0 may only be used as a directive, adding the directory from which the current Prolog source is loaded at the head of the Python search path. If py_add_lib_dir/1 or py_add_lib_dir/2 are used in a directive and the given directory is not absolute, it is resolved against the directory holding the current Prolog source.
822:- multifile system:term_expansion/2. 823 824systemterm_expansion((:- py_add_lib_dir(Dir0)), 825 (:- initialization(py_add_lib_dir(Dir, first), now))) :- 826 \+ is_absolute_file_name(Dir0), 827 prolog_load_context(directory, CWD), 828 absolute_file_name(Dir0, Dir, [relative_to(CWD)]). 829systemterm_expansion((:- py_add_lib_dir(Dir0, Where)), 830 (:- initialization(py_add_lib_dir(Dir, Where), now))) :- 831 \+ is_absolute_file_name(Dir0), 832 prolog_load_context(directory, CWD), 833 absolute_file_name(Dir0, Dir, [relative_to(CWD)]), 834 absolute_file_name(Dir0, Dir). 835 836py_add_lib_dir(Dir) :- 837 py_add_lib_dir(Dir, first). 838 839py_add_lib_dir(Dir, Where) :- 840 absolute_file_name(Dir, AbsDir), 841 prolog_to_os_filename(AbsDir, OSDir), 842 ( py_call(sys:path, Dirs0), 843 memberchk(OSDir, Dirs0) 844 -> true 845 ; Where == last 846 -> py_call(sys:path:append(OSDir), _) 847 ; Where == first 848 -> py_call(sys:path:insert(0, OSDir), _) 849 ; must_be(oneof([first,last]), Where) 850 ). 851 852 853 /******************************* 854 * CALLBACK * 855 *******************************/ 856 857:- dynamic py_call_cache/8 as volatile. 858 859:- meta_predicate py_call_string( , , ). 860 861% py_call_string(:String, +DictIn, -Dict) is nondet. 862% 863% Support janus.query_once() and janus.query(). Parses String into a goal 864% term. Next, all variables from the goal term that appear in DictIn 865% are bound to the value from this dict. Dict is created from the 866% remaining variables, unless they start with an underscore (e.g., 867% `_Time`) and the key `truth. On success, the Dict values contain 868% the bindings from the answer and `truth` is either `true` or 869% `Undefined`. On failure, the Dict values are bound to `None` and the 870% `truth` is `false`. 871% 872% Parsing and distributing the variables over the two dicts is cached. 873 874py_call_string(M:String, Input, Dict) :- 875 py_call_cache(String, Input, TV, M, Goal, Dict, Truth, OutVars), 876 !, 877 py_call(TV, M:Goal, Truth, OutVars). 878py_call_string(M:String, Input, Dict) :- 879 term_string(Goal, String, [variable_names(Map)]), 880 unbind_dict(Input, VInput), 881 exclude(not_in_projection(VInput), Map, OutBindings), 882 dict_create(Dict, bindings, [truth=Truth|OutBindings]), 883 maplist(arg(2), OutBindings, OutVars), 884 TV = Input.get(truth, 'PLAIN_TRUTHVALS'), 885 asserta(py_call_cache(String, VInput, TV, M, Goal, Dict, Truth, OutVars)), 886 VInput = Input, 887 py_call(TV, M:Goal, Truth, OutVars). 888 889py_call('NO_TRUTHVALS', M:Goal, Truth, OutVars) => 890 ( call(M:Goal) 891 *-> bind_status_no_no_truthvals(Truth) 892 ; Truth = @false, 893 maplist(bind_none, OutVars) 894 ). 895py_call('PLAIN_TRUTHVALS', M:Goal, Truth, OutVars) => 896 ( call(M:Goal) 897 *-> bind_status_plain_truthvals(Truth) 898 ; Truth = @false, 899 maplist(bind_none, OutVars) 900 ). 901py_call('DELAY_LISTS', M:Goal, Truth, OutVars) => 902 ( call_delays(M:Goal, Delays) 903 *-> bind_status_delay_lists(Delays, Truth) 904 ; Truth = @false, 905 maplist(bind_none, OutVars) 906 ). 907py_call('RESIDUAL_PROGRAM', M:Goal, Truth, OutVars) => 908 ( call_delays(M:Goal, Delays) 909 *-> bind_status_residual_program(Delays, Truth) 910 ; Truth = @false, 911 maplist(bind_none, OutVars) 912 ). 913 914not_in_projection(Input, Name=Value) :- 915 ( get_dict(Name, Input, Value) 916 -> true 917 ; sub_atom(Name, 0, _, _, '_') 918 ). 919 920bind_none(@none). 921 922bind_status_no_no_truthvals(@true). 923 924bind_status_plain_truthvals(Truth) => 925 ( '$tbl_delay_list'([]) 926 -> Truth = @true 927 ; py_undefined(Truth) 928 ). 929 930bind_status_delay_lists(true, Truth) => 931 Truth = @true. 932bind_status_delay_lists(Delays, Truth) => 933 py_call(janus:'Undefined'(prolog(Delays)), Truth). 934 935bind_status_residual_program(true, Truth) => 936 Truth = @true. 937bind_status_residual_program(Delays, Truth) => 938 delays_residual_program(Delays, Program), 939 py_call(janus:'Undefined'(prolog(Program)), Truth). 940 941py_undefined(X) :- 942 py_call(janus:undefined, X). 943 944unbind_dict(Dict0, Dict) :- 945 dict_pairs(Dict0, Tag, Pairs0), 946 maplist(unbind, Pairs0, Pairs), 947 dict_pairs(Dict, Tag, Pairs). 948 949unbind(Name-_, Name-_) :- 950 sub_atom(Name, 0, 1, _, Char1), 951 char_type(Char1, prolog_var_start), 952 !. 953unbind(NonVar, NonVar). 954 955 956 /******************************* 957 * SUPPORT PYTHON CALLS * 958 *******************************/ 959 960:- public 961 px_cmd/3, 962 px_call/4, 963 px_comp/7. 964 965% These predicates are helpers for the corresponding Python functions 966% in janus.py. 967 968 969% px_call(+Input:tuple, +Module, -Pred, -Ret) 970% 971% Supports px_qdet() and apply(). Note that these predicates 972% explicitly address predicates in a particular module. For meta 973% predicates, this implies they also control the context module. This 974% leads to ``janus.cmd("consult", "consult", file)`` to consult _file_ 975% into the module `consult`, which is not what we want. Therefore we 976% set the context module to `user`, which is better, but probably also 977% not what we want. 978 979px_call(-(), Module, Pred, Ret) => 980 @(call(Module:Pred, Ret), user). 981px_call(-(A1), Module, Pred, Ret) => 982 @(call(Module:Pred, A1, Ret), user). 983px_call(-(A1,A2), Module, Pred, Ret) => 984 @(call(Module:Pred, A1, A2, Ret), user). 985px_call(-(A1,A2,A3), Module, Pred, Ret) => 986 @(call(Module:Pred, A1, A2, A3, Ret), user). 987px_call(-(A1,A2,A3,A4), Module, Pred, Ret) => 988 @(call(Module:Pred, A1, A2, A3, A4, Ret), user). 989px_call(Tuple, Module, Pred, Ret) => 990 compound_name_arguments(Tuple, _, Args), 991 append(Args, [Ret], GArgs), 992 Goal =.. [Pred|GArgs], 993 @(Module:Goal, user). 994 995px_cmd(Module, Pred, Tuple) :- 996 ( compound(Tuple) 997 -> compound_name_arguments(Tuple, _, Args), 998 Goal =.. [Pred|Args] 999 ; Goal = Pred 1000 ), 1001 @(Module:Goal, user). 1002 1003px_comp(Module, Pred, Tuple, Vars, Set, TV, Ret) :- 1004 length(Out, Vars), 1005 ( compound(Tuple) 1006 -> compound_name_arguments(Tuple, _, Args), 1007 append(Args, Out, GArgs), 1008 Goal =.. [Pred|GArgs] 1009 ; Goal =.. [Pred|Out] 1010 ), 1011 compound_name_arguments(OTempl0, -, Out), 1012 tv_goal_and_template(TV, @(Module:Goal, user), FGoal, OTempl0, OTempl), 1013 findall(OTempl, FGoal, Ret0), 1014 ( Set == @true 1015 -> sort(Ret0, Ret) 1016 ; Ret = Ret0 1017 ). 1018 1019:- meta_predicate 1020 call_delays_py( , ). 1021 1022% 0,1,2: TruthVal(Enum) from janus.py 1023tv_goal_and_template('NO_TRUTHVALS', 1024 Goal, Goal, Templ, Templ) :- !. 1025tv_goal_and_template('PLAIN_TRUTHVALS', 1026 Goal, ucall(Goal, TV), Templ, -(Templ,TV)) :- !. 1027tv_goal_and_template('DELAY_LISTS', 1028 Goal, call_delays_py(Goal, TV), Templ, -(Templ,TV)) :- !. 1029tv_goal_and_template(Mode, _, _, _, _) :- 1030 domain_error("px_comp() truth", Mode). 1031 1032:- public 1033 ucall/2, 1034 call_delays_py/2. 1035 1036ucall(Goal, TV) :- 1037 call(Goal), 1038 ( '$tbl_delay_list'([]) 1039 -> TV = 1 1040 ; TV = 2 1041 ). 1042 1043call_delays_py(Goal, PyDelays) :- 1044 call_delays(Goal, Delays), 1045 ( Delays == true 1046 -> PyDelays = [] 1047 ; comma_list(Delays, Array), 1048 maplist(term_string, Array, PyDelays) 1049 ). 1050 1051 1052 /******************************* 1053 * PYTHON I/O * 1054 *******************************/ 1055 1056% py_write(+Stream, -String) is det. 1057% py_readline(+Stream, +Size, +Prompt, +Line) is det. 1058% 1059% Called from redefined Python console I/O to write/read using the 1060% Prolog streams. 1061 1062:- '$hide'((py_write/1, 1063 py_readline/4)). 1064 1065py_write(Stream, String) :- 1066 notrace(format(Stream, '~s', [String])). 1067 1068py_readline(Stream, Size, Prompt, Line) :- 1069 notrace(py_readline_(Stream, Size, Prompt, Line)). 1070 1071py_readline_(Stream, _Size, Prompt, Line) :- 1072 prompt1(Prompt), 1073 read_line_to_string(Stream, Read), 1074 ( Read == end_of_file 1075 -> Line = "" 1076 ; string_concat(Read, "\n", Line), 1077 py_add_history(Read) 1078 ). 1079 1080py_add_history(Line) :- 1081 ignore(catch(prolog:history(user_input, add(Line)), _, true)). 1082 1083 1084 /******************************* 1085 * COMPILING * 1086 *******************************/ 1087 1088% py_consult(+File, +Data, +Module) is det. 1089% 1090% Support janus.consult(file, data=None, module='user'). 1091 1092:- public py_consult/3. 1093py_consult(File, @none, Module) => 1094 consult(Module:File). 1095py_consult(File, Data, Module) => 1096 setup_call_cleanup( 1097 open_string(Data, In), 1098 load_files(Module:File, [stream(In)]), 1099 close(In)). 1100 1101 1102 /******************************* 1103 * MESSAGES * 1104 *******************************/ 1105 1106:- multifile 1107 prolog:error_message//1, 1108 prolog:message//1. 1109 1110prologerror_message(python_error(Class, Value, _Stack)) --> 1111 { py_str(Value, Message) 1112 }, 1113 [ 'Python ', ansi(code, "'~w'", [Class]), ':', nl, 1114 ' ~w'-[Message] 1115 ]. 1116 1117prologmessage(janus(Msg)) --> 1118 message(Msg). 1119 1120message(version(V)) --> 1121 [ 'Janus embeds Python ~w'-[V] ]. 1122message(venv(Dir, _EnvSiteDir)) --> 1123 [ 'Janus: using venv from ~p'-[Dir] ]. 1124message(venv(no_site_package_dir(VEnvDir, Dir))) --> 1125 [ 'Janus: venv dirrectory ~p does not contain ~p'-[VEnvDir, Dir] ]. 1126message(py_shell(no_janus)) --> 1127 [ 'Janus: py_shell/0: Importing janus into the Python shell requires Python 3.10 or later.', nl, 1128 'Run "', ansi(code, 'from janus import *', []), '" in the Python shell to import janus.' 1129 ]
Call Python from Prolog
This library implements calling Python from Prolog. It is available directly from Prolog if the janus package is bundled. The library provides access to an embedded Python instance. If SWI-Prolog is embedded into Python using the Python package
janus-swi
, this library is provided either from Prolog or from the Python package.Normally, the Prolog user can simply start calling Python using py_call/2 or friends. In special cases it may be needed to initialize Python with options using py_initialize/3 and optionally the Python search path may be extended using py_add_lib_dir/1. */