:- use_module(library(janus)). here. :- initialization source_file(here, File), file_directory_name(File, Dir), py_add_lib_dir(Dir, first). bench(N) :- py_version, % Load Python bench_echo_list(N), bench_pass_list(N), bench_py_call_int(N), bench_py_call_sumlist(N), bench_call_prolog(N), bench_iter_prolog(N, _), bench_iter_py(N), bench_px_cmd(N). bench_py_call_int(N) :- ansi_format(bold, 'Calling python int() ~D times~n', [N]), time(forall(between(1,N,_I), py_call(demo:int(), _L))). bench_py_call_sumlist(N) :- ansi_format(bold, 'Calling python sumlist3(5,[1,2,3]) ~D times~n', [N]), time(forall(between(1,N,_I), py_call(demo:sumlist3(5,[1,2,3]), _L))). bench_iter_prolog(N, Sum) :- ansi_format(bold, 'Iterate over Prolog goal with ~D answers~n', [N]), time(py_call(demo:bench_iter(N), Sum)). bench_call_prolog(N) :- ansi_format(bold, 'Call Prolog predicate from Python ~D times~n', [N]), time(py_call(demo:bench_call(N), _)). bench_pass_list(N) :- ansi_format(bold, 'Pass list with ~D integers to Python~n', [N]), numlist(1, N, L), time(py_call(demo:echo(L))). bench_echo_list(N) :- ansi_format(bold, 'Echo list with ~D integers to Python~n', [N]), numlist(1, N, L), time(py_call(demo:echo(L), _)). bench_iter_py(N) :- ansi_format(bold, 'Iterating over Python range(0,~d) from Prolog~n', [N]), time(forall(py_iter(range(0,N), _), true)). bench_px_cmd(N) :- ansi_format(bold, 'Call px_cmd("true") ~D times', [N]), time(py_call(demo:bench_px_cmd(N))). py_thread(Id) :- thread_self(Self), ( atom(Self) -> Id = Self ; thread_property(Self, id(Id)) ).