Prolog universal server

Hello all,
I’ve just stumbled on this short blog post about a universal server in erlang.
The idea is that the erlang server can morphe into any given remote code.

I was wondering if something similar could be achieved in prolog ?
Maybe with pengines ? although I could never really grok it…

I’ve always dreamed of being able to have a cluster of prolog interpreters on which I could run distributed queries ^^

That is basically why @torbjorn.lager started Pengines and later wrote the WebProlog proposal. I’m probably to blame for dealing with most of the engineering challenges to make Pengines work but never really picked up WebProlog because Pengines did for 90% what I wanted and I didn’t have the time to restart. Also Pengines has quite a few users and replacing it with something new, although better designed is always hard.

Notably between Polog processes, Pengines are fun:

?- pengine_rpc('https://swish.swi-prolog.org', member(X, [a,b,c])).
X = a ;
X = b ;
X = c.

The real fun starts that we can transfer code. Given locally

planet(mercury).
planet(venus).
planet(earth).
planet(mars).
planet(jupiter).
planet(saturn).
planet(uranus).
planet(neptune).

We can count our planets (stupid plan) using

?- pengine_rpc('https://swish.swi-prolog.org',
               aggregate_all(count, planet(_), Count),
               [ src_predicates([planet/1])]).
Count = 8
1 Like

I did not realize you could send a predicate with src_predicates !

One thing I’ve tried but did not manage to get working is to send a predicate using clpfd constraints.
Something like:

:- use_module(library(clpfd)).

problem(X, Y, Z) :-
    [X, Y] ins 0..10,
    Z #= X + Y,
    label([X, Y, Z]).

Here is what I got:

?- pengine_rpc('http://localhost:8000',
               problem(X, Y, Z),
               [ src_predicates([problem/3])]).
ERROR: procedure `'c78328f9-c284-48eb-b657-480e8b574bc9':problem(A,B,C)' does not exist
^  Exception: (11) setup_call_catcher_cleanup(pengines:pengine_create([ask(problem(_12746, _12
748, _12750)), template(v(_12746, _12748, _12750)), server('http://192.168.1.13:8000'), id('c7
8328f9-c284-48eb-b657-480e8b574bc9'), timeout(300), src_text(...)]), pengines:wait_event(v(_12
746, _12748, _12750), destroy(true), [listen('c78328f9-c284-48eb-b657-480e8b574bc9'), timeout(
300), src_text("problem(X, Y, Z) :-\n    [X, Y]ins 0..10,\n    (   integer(Z)\n    ->  (   int
eger(X),\n            integer(Y)\n        ->  Z=:=X+Y\n        ;   A=Z,\n            clpfd:clp
fd_equal(A, X+Y)\n        )\n    ;   integer(X),\n        integer(Y)\n    ->  (   var(Z)\n    
    ->  Z is X+Y\n        ;   A is X+Y,\n            clpfd:clpfd_equal(Z, A)\n        )\n    ;
   clpfd:clpfd_equal(Z, X+Y)\n    ),\n    label([X, Y, Z]).\n\n")]), _13748, pengines:pengine_
destroy_and_wait(destroy(true), 'c78328f9-c284-48eb-b657-480e8b574bc9', _13748)) ? abort
% Execution Aborted

However, if I add a :- use_module(library(clpfd)). to my server script, it works.
Is there a way to transmit modules too with pengines_rpc ?

In general it won’t work well for code that relies on libraries or source code transformation. With some luck it might be possible to get some of this working. Sending the library itself is not an option. library(clpfd) does not pass the sandbox safety tests. We believe it is safe anyway, so the API is defined to be safe.

In general, the transfer does not deal with dependencies. Feel free to make a PR to make it more flexible :slight_smile:

Is there a way to disable the sandbox ?

I would like to be able to call predicates like concurrent_and in a pengine and it won’t allow me:

?- pengine_rpc('http://localhost:8000',
               concurrent_and(member(X, [a, b, c]), Y=X), []).
ERROR: No permission to call sandboxed `message_queue_create(_11160,_11162)'
^  Exception: (11) setup_call_catcher_cleanup(pengines:pengine_create([ask(concurrent_and(memb
er(_1058, [a, b|...]), _1064=_1058)), template(v(_1058, _1064)), server('http://localhost:8000
'), id('dbb2b851-601e-4be3-a5a2-756abf281cdc'), timeout(300)]), pengines:wait_event(v(_1058, _
1064), destroy(true), [listen('dbb2b851-601e-4be3-a5a2-756abf281cdc'), timeout(300)]), _1732, 
pengines:pengine_destroy_and_wait(destroy(true), 'dbb2b851-601e-4be3-a5a2-756abf281cdc', _1732
)) ? abort
% Execution Aborted

Yes, but you have to run your own server. If I recall correctly the sandbox is by default enabled of you enforce login. You can also disable it without login, but I’ll restrict that to a local network behind a good firewall :slight_smile: If you enable login you get the usual trouble with authentication. Just about anything can be configured from simple basic HTTP authentication to obligatory TLS client certificates.

I’m running my own server with the following script I found in another discourse thread:

:- use_module(library(http/http_server)).
:- use_module(library(clpfd)).
:- use_module(library(pengines)).

server(Port) :-
    http_server([port(Port)]).

How would I disable the sandbox in this case ?

I’m afraid most of this is not well documented :frowning:

You can find a lot of configuration scenarios in the SWISH sources where there is a directory config-available.

Looking a pengines.pl we find pengine_not_sandboxed/1, so, with login you can disable the sandbox using

:- multifile pengines:not_sandboxed/2.
pengines:not_sandboxed(_, _).

I think you can fake login by defining pengines:authentication_hook/3.

Note that using SWISH as starting point might make sense to simplify the configuration and play interactively. Of course, just pengines is a lot more lightweight.

In my case, I’m aiming more for something akin to cluster computing.

This urge stems from when I discovered that I could speed up incredibly a clpfd constraint problem labelling by using the predicate concurrent_and/2 by labelling first a few variables and finishing the labelling of other variables in parallel.

With you help, I managed to write this script:

:- use_module(library(http/http_server)).
:- use_module(library(clpfd)).
:- use_module(library(pengines)).

n_queens(N, Qs) :-
        length(Qs, N),
        Qs ins 1..N,
        safe_queens(Qs).

safe_queens([]).
safe_queens([Q|Qs]) :- safe_queens(Qs, Q, 1), safe_queens(Qs).

safe_queens([], _, _).
safe_queens([Q|Qs], Q0, D0) :-
        Q0 #\= Q,
        abs(Q0 - Q) #\= D0,
        D1 #= D0 + 1,
        safe_queens(Qs, Q0, D1).

% cluster('http://192.168.1.12:8001', 12).
cluster('http://localhost:8000', 7).

create_cluster(Cluster) :-
   findall(C, create_cluster_(C), Cs),
   append(Cs, Cluster).
create_cluster_(Cluster) :-
   cluster(Server, Cpus),
   length(Cluster, Cpus),
   maplist(=(Server), Cluster).

create_cluster_queue(ClusterSize) :-
   create_cluster(Cluster),
   length(Cluster, ClusterSize),
   message_queue_create(Queue, [alias(cluster)]),
   maplist(thread_send_message(Queue), Cluster).

destroy_cluster_queue :-
   message_queue_destroy(cluster).

strip_modules(MGs, Gs) :-
   maplist(strip_module, MGs, _, Gs).

run(Goal) :-
   copy_term(Goal, Copy, MGs),
   strip_modules(MGs, Gs),
   (  Gs = [G | OtherGs]
   -> foldl([A, B, (A, B)]>>(true), OtherGs, G, Conjuction)
   ;  Conjuction = true
   ),
   setup_call_cleanup(
      thread_get_message(cluster, Server),
      pengine_rpc(Server, (Conjuction, Copy)),
      thread_send_message(cluster, Server)),
   Goal = Copy.

server(Port) :-
    http_server([port(Port)]).

with this you can add nodes with the predicate cluster/2 and use the create_cluster_queue to “create” a cluster (which is just a message queue with server urls).

Then, the wrapper predicate run/1 can be used to run a goal on a pengine in the cluster.
The particularity of the run/1 predicate is that it can deal with attributed variables and replicate them in the pengine.

Finally, this compose with concurrent_and/2 to label the n_queens problems in parallel on multiple nodes:

?- %distribute the script and start a server on each node
?- server(8000).

?- %create the cluster queue
?- create_cluster_queue(ClusterSize).
?- % then you can run your labeling problem on multiple nodes
?- n_queens(20, [A | Bs]), concurrent_and(label([A]), run(label(Bs)), [threads($ClusterSize)]).
A = 5,
Bs = [1, 4, 6, 3, 9, 14, 18, 15, 19|...],
ClusterSize = 7 .

If anyone asks if this is faster than a single process labeling, I have no idea…
I was just interested to see if this was even possible at all :slight_smile:

However, I have a termination problem.
If I abort after the first solution, the interpreter will take a long time to return the prompt.
I believe thread cancellation is not working well somewhere…