Using `format/2` with attributed variable on a pengine

An simple example of of outputting a clpBNR interval variable with format/2:

?- {X>=1}, format('interval(~w)',X).
interval(_2428{real(1,1.0Inf)})
X::real(1, 1.0Inf).

If I run the same example on a local pengine using a test predicate local_query/1, the received output message doesn’t contain the attribute:

?- local_query(({X>=1}, format('interval(~w)',X))).
interval(_13136)
> {_4996{real(1,1.0Inf)}>=1},format('interval(~w)',_4996{real(1,1.0Inf)}).
true.

(The content of the output line with the > prefix is from the success response, a copy of the query.)

freeze has a similar behaviour (reproducible on SWISH):

?- freeze(X,X>=1), format('frozen(~w)',X).
frozen(_7708{freeze(_7708, user:(_7708>=1))})
freeze(X, X>=1).

?- local_query((freeze(X,X>=1), format('frozen(~w)',X))).
frozen(_1688)
> freeze(_9884{freeze(_9884, 'feaf0cef-3307-4650-a59a-de9f8f254df0':(_9884>=1))},_9884{freeze(_9884, 'feaf0cef-3307-4650-a59a-de9f8f254df0':(_9884>=1))}>=1),format('frozen(~w)',_9884{freeze(_9884, 'feaf0cef-3307-4650-a59a-de9f8f254df0':(_9884>=1))}).
true.

Bug or feature? Any workaround?

What is this predicate?

A predicate I wrote to locally test queries on a pengine:

module(test_local_pengine)
:- module(test_local_pengine,
	[
	local_query/1
	]).
	
:- use_module(library(pengines)).

local_query(Query) :-
	nb_setval('test_local_pengine:query',Query),
	local_create.	

local_create :-
	pengine_create([]),
	pengine_event_loop(local_handle,[]).  % on separate thread

local_handle(create(ID,_)) :- !,
	nb_getval('test_local_pengine:query',Query),
	pengine_ask(ID,Query,[]).	


local_handle(success(ID,Terms,More)) :-
% %local_handle(success(ID,Terms,_Projection,_Time,More)) :-
	print_message(banner, local_handle_result(Terms)),
	(More == true -> pengine_next(ID,[]) ; pengine_destroy(ID)).
	
local_handle(failure(ID)) :-
	print_message(banner, local_handle_result(fail)),
	pengine_destroy(ID).
	
local_handle(error(ID,Exception)) :-
	print_message(error, local_handle_output(Exception)),
	pengine_destroy(ID).
	
local_handle(output(_ID,Term)) :-
	print_message(information, local_handle_output(Term)).
	
local_handle(destroy(ID)) :-
	print_message(warning, local_handle_output(destroy(ID))).
	
local_handle(Event) :-
	print_message(warning, local_handle_unexpected(Event)).

	
prolog:message(local_handle_result(Result)) -->
	['> ~p.' - Result].
	
prolog:message(local_handle_output(Output)) -->
	['~w' - Output].
	
prolog:message(local_handle_unexpected(Event)) -->
	['Unexpected ~w' - Event].

Thanks. I think it has to do with the write_attributes flag that is different in the Pengines thread than in your main thread. I guess this flag can be declared safe. It calls user:attr_portray_hook/2 when set to portray, but sandboxed users cannot add to that predicate.

I can verify this. So I’ll have to include setting the write_attributes flag in the thread level initialization code on the server. (I already do this for several arithmetic flags.)

Am I right to conclude that a pengine starts with a copy of the default settings of all prolog flags?

I can declare the write_attributes_flag safe, but I would think this is best done in sandbox. (clpBNR provides a attr_portray_hook for its intervals).

Pengines are created using thread_create_in_pool/4 which in turn use thread_create/3 using the option inherit_from(main), so the initial flags are the flags as they appear in the main thread (at least, I hope).

You mean using thread_initialization/1? That is fine for a server only running your code, but for the public SWISH this would mean all Pengines run with the flag setting you need. That is not acceptable. We need something that causes :- use_module(library(clpBNR)). to set the flags, even if the module is already loaded. Or some other trick to set these flags lazily. The latter would be nice. If not possible we have to find a trick to make the first possible. Not sure how … Well, maybe using a term_expansion/2 rule that expands the use_module/1 call to also set the flags?

As flags are not bound to a module, this affects the whole server anyway.

I don’t think this is what I’m seeing - perhaps an artifact of my test environment:

?- current_prolog_flag(write_attributes,A).
A = portray.

?- local_query(current_prolog_flag(write_attributes,A)).
> current_prolog_flag(write_attributes,ignore).
Warning: destroy(e7085974-c05c-470b-940c-f4bc6dec75ed)
true.

I don’t use thread_initialization; perhaps I should (?). I initialize a selected set of flags, e.g., some arithmetic flags, when triggered by an undefined global variable on the first call which might create clpBNR attributed variable. I guess that would be considered a lazy set. (I just added write_attributes to that selected set.)

From experimentation, it also appears that setting flags in a pengine doesn’t affect any other pengines, so as long as these flags are lazily set as above, everything should be good.That means I shouldn’t be setting these flags at module initialization time and only use the lazy mechanism described above.

But flags do seem to be bound to a pengine/thread, so setting them there shouldn’t affect the whole server (?).

So all is well for formatted output of attributed variables if the write_attributes flag is set to portray in the query pengine, which also means it has to be declared a “safe” flag. Note this doesn’t appear to affect the top level answer format of attributed variables, presumably because it’s not running in the query pengine(?).

This raises another question. If a pengine inherits its initial environment flag values from its parent, and subsequent settings of those flags are only visible in that pengine, i.e., not visible to other pengines, what are the requirements to deem a flag “unsafe”? I don’t understand the subtleties of many of the “changeable” environment flags, but scanning the list, none are obviously unsafe to me in a pengine-local context. (Well maybe you don’t want errors to invoke the debugger (flag debug_on_error), but if it’s pengine-local??)

The SWISH toplevel printing goes through library(pengines_io), which eventually uses library(http/term_html), term//2 to render the term using HTML. term//2 implements write_term/3, but does not have the attributes(format) option. That is considered obsolete and (also) the normal toplevel uses copy_term/3 to turn attributes into goals. And indeed, another problem is that the translation of the result to an HTML result is done in the HTTP handler thread rather than in the Pengine that simply returns the result as a term.

Most flags are indeed fine. But, there are flags that affect the global state, there are flags that affect modules and flags that affect resource limits. None of these may be considered safe. The general approach of the sandbox library is to whitelist rather than blacklist.

The first questions is why can’t clpBNR support copy_term/3, so it is in sync with the other constraint libraries?

I believe it does in so far as it implements attribute_goals//1 which is required to support copy_term/3. So if this is the basis, for generating the answer output in SWISH, I think all should be fine.

But there is one caveat: as an answer, the output of the clpBNR constraint network can be overwhelming. So there is a custom environment flag clpBNR_verbose (default=false) which optionally produces an abbreviated answer containing just the ranges of the query variables (obtained using the user:expand_answer hook). I’m not sure how this would be supported in a SWISH environment.

Do you mean the application global state or the pengine global state? If the former, are there a couple of examples where that happens? (Must be some side-effect in C managed data, which is truly global? Or there’s something else going on with environment flags I don’t understand.)

And I think this is quite reasonable for predicates/primitives. But It’s less clear to me why this is so for flags, where flag updates are scoped to the pengine. And it seems even less justified when it comes to global variables, which are thread-local by design, IIRC.

My objective is to make the SWISH UI for clpBNR as close as possible to the what the user would see using SWIP, modulo a couple of developer support features (requires pengine-local debug topics). That looks achievable. The rest of this discussion is really just about simplifying the job of sandboxing for future similar activities and reducing the overhead of maintaining an (incomplete) white list of flags in the sandbox module - your call.

:+1:

Good question … The SWISH toplevel is distinct from the Prolog one, although it does reuse a lot of the regular toplevel code. It also worked for systems like CHR and s(CASP), so it should be possible. It may require extending SWISH a bit though. The relevant stuff is mostly in lib/trace.pl of the swish sources. This essentially packs additional information such as the well founded semantics delay list in additional variables that it adds to the projection (bindings). Next, `web/js/answer.js deals with these variables. Possibly you can either reuse this, add another hack for clpBNR or, better, try to generalize it. I hope you installed a local copy of SWISH to experiment with?

Various of the flags call some C hook when changed, and some even when queried (something that should be generalized one day). There are not many that have global effect but they exist. An example is agc_margin, controlling the timing of the atom garbage collector. As the atom table is shared, the effects of this flag are global. Setting it to too small values with make the system very slow, setting it too large will eat all memory. Other flags are thread specific, but tune resource limits. Also libraries may define flags that select between safe and unsafe behavior. It is hard to be exhaustive, so, as with predicates, whitelisting the safe ones is the safe choice. As is, few are declared safe. Many more are, but typically there is not much need to change any of them. Just submit a PR with the ones clpBNR needs. Note that libraries are normally loaded at SWISH startup time in the main thread. This implies that these libraries should not change flags that have global effect (e.g., we do not want all Pengines to map float overflows to infinity but we want to keep the default Prolog behavior to raise an exception).

Note that adding clpBNR shall typically add the system as a git submodule to add it as a local package and have a config-available/clpBNR.pl that load the library and sets up anything it needs to operate properly inside SWISH.

So this is a complication I had hoped to avoid and will take some effort.

write_attributes is the only relevant non-safe flag at this point. Other currently safe flags, like the arithmetic flags, obviously require other than the default values, but changing them is done on “first call”, rather than library load time, so I think that’s the desired behaviour.

Not really sure what this means. Does the current clpBNR git structure meet the requirement, or am I missing the point.

From swish’s lib/trace.pl:

%!	pre_context(Name, Goal, Var) is semidet.
%!	post_context(Name, Goal, Var) is semidet.
%
%	Multifile hooks to  extract  additional   information  from  the
%	Pengine, either just before Goal is   started or after an answer
%	was  produced.  Extracting  the  information   is  triggered  by
%	introducing a variable with a reserved name.

:- multifile
	pre_context/3,
	post_context/1,
	post_context/3,
	post_context/4.

I’m guessing this is where I should be starting, but I can’t find anything that documents what these hooks do. Any doc or examples that might help?

Added.

clpBNR is (I think( structured as a package, so that should be fine. There are roughly two ways to deal with packages. One is to install them as user. The other is to make them submodules (provided they are available as a git module) of the main project and install them locally. That keeps packages strictly local to a project and gives full version control over a package as it is used in some larger project. SWISH does that.

The s(CASP) SWISH integration is here: https://github.com/SWI-Prolog/sCASP/blob/5d50348852e0930a34e5ee01744bee3c25ff105b/prolog/scasp/swish.pl The integration makes the model and justification visible. I’m afraid all this is not trivial :frowning:

Thanks. I see it’s in SWIP 9.1.20 so I’ll do my final testing on thta.

The package actually contains two modules - clpBNR and clpBNR_utilities. I assume the install will include both.

Note: the last post on Sandboxing modules - #3 by ridgeworks discusses a minor change to library(simplex) to make its maximize/3 and minimize/3 accessible on SWISH. The fix is fairly simple and at some point I’ll try to generate a PR.

If this is the solution, I’ll give a hard pass. I’ll just add the inability to view the constraint network at the toplevel to list of things not supported on SWISH. It’s primarily a developer feature anyway, so there are a few of these on that list.

:+1:

I don’t know. There could be others. So far, the most problematic systems have been CHR and sCASP. Both because they leave stuff relevant to the answer in Prolog global variables. That doesn’t seem to be the problem for your case. Roughly the idea for both was to reflect the values of these global variables as pseudo bindings, i.e., add a reserved variable to the answer that caries the required information.

I’ve pushed a new version (0.11.3) of clpBNR to github (GitHub - ridgeworks/clpBNR: CLP(BNR) module for SWI-Prolog) with the necessary changes I know about to make it SWISH compliant. It’s been tested with a local pengine and functions as expected modulo some developer centric features that rely on debug topics. It has not been tested with a local copy of SWISH - I haven’t figured out how to do that based on the doc in the SWISH repo. When you have a chance, please review what’s there and let me know if there’s anything more to be done at my end to move this forward.

So I tried to generate a PR for the simplex module and the update got included in the existing Draft updated doc for profiler by ridgeworks · Pull Request #1144 · SWI-Prolog/swipl-devel · GitHub.

Not sure what I did wrong and what to do about it.

You should make PRs from local branches. That makes it much easier to keep them clean and separated. So,

  • Make sure your master branch simply points at origin/master

  • Make sure it is up-to-date. If you did editing in master before, move this work to another
    branch (git branch mybranch) to avoid loosing it. The run

     git fetch origin
     git reset --hard origin/master
    

    Note that the git reset --hard looses any changes, so make sure these are saved before.

  • Now, create a topic branch

     git checkout -b mytopic
     <hack away>
     <commit>
     git push myfork mytopic
     <open link for PR and complete>
    

Once the PR is merged, go back to master, pull and optionally delete the mytopic branch. If it doesn’t get merged and you want to resync, gi to master, pull, go back to your branch and run

     git rebase master

This way your modifications are kept cleanly separated.

Anyway, I fetched your master branch and used git cherry-pick <commit> to merge it.

I don’t really use or understand the GIT CLI, which probably means I really don’t understand GIT. Having more than on outstanding PR/branch is a recipe for disaster, so I’m just going to try and avoid that going forward.

Since #1144 is still active, I’ll just close and purge that if I have to submit some future PR.