swish
swish copied to clipboard
set_prolog_flag sometimes has no effect
When I create an empty SWISH program and insert:
:- use_module(library(clpb)).
:- set_prolog_flag(clpb_residuals, bdd).
then everything works exactly as expected: Posting a query like ?- sat(X+Y).
emits a BDD.
I then want to get back the default behaviour of library(clpb)
and change the atom bdd
to default
, i.e., let the program consist of:
:- use_module(library(clpb)). :- set_prolog_flag(clpb_residuals, default).
The flag seems to be correctly set as expected, which I can verify in the SWISH "toplevel":
?- current_prolog_flag(clpb_residuals, X). X = default
However, posting a query like sat(X+Y)
still emits a BDD:
?- sat(X+Y). clpb : '$clpb_bdd'([node(2)-(v(X, 0)->true;node(1)), node(1)-(v(Y, 1)->true;false)])
The analogous interaction works exactly as intended on the normal toplevel:
?- [library(clpb)]. true. ?- set_prolog_flag(clpb_residuals, bdd). true. ?- sat(X+Y). clpb:'$clpb_bdd'([node(2)- (v(X, 0)->true;node(1)), node(1)- (v(Y, 1)->true;false)]). ?- set_prolog_flag(clpb_residuals, default). true. ?- sat(X+Y). sat(X=\=X*Y#Y).
This is connected to #25.
Yip. This is because the toplevel answer preparation is not happening in the Pengine that computes the answer, but in the HTTP infrastructure around it, while flags are thread-specific. Your schema computing the BDD from the residual goals could in theory work. I see some remarks on the performance of this. How serious is this?
The alternative might be to do the copy_term/3 in '$swish wrapper'/2. That smells a little hacky too.
I managed to get the drawing of the BDD working from "normal" sat/1
residuals, using the new varsnumbers_names/3
. Please see the repository.
However, I still need a way for users to set clpb_residuals
to bdd
in SWISH in such a way that it affects library(clpb)
. This is because the projection from BDDs to sat/1
residuals (!) that is done by library(clpb)
can be extremely costly. As a simple test case, please try the easy looking CLP(B) goal:
?- length(Ls, 20), sat(card([4],Ls)).
<wait>
Almost all the time in this case is spent in the projection to sat/1
goals! The BDD is actually quite straight-forward, and can be easily shown with graphviz. You can see the BDD with:
?- set_prolog_flag(clpb_residuals, bdd). true. ?- length(Ls, 20), sat(card([4],Ls)). Ls = ... clpb:'$clpb_bdd'([node(83)- (v(_G6802, 0)->node(82); ...)
I have written the renderer in such a way that both kinds of residual goals are rendered correctly. But in many cases, we cannot afford to let CLP(B) produce sat/1
goals first. Instead, we need to circumvent the projection by setting this flag, which is the reason it is there in the first place.
Note that when working on the default sat/1
goals, the renderer currently has to do the work that CLP(B) has already done again: CLP(B) processes sat/1
constraints, creates BDDs, then shows (often heavily simplified) sat/1
residuals (sometimes a very costly projection!), then the renderer sees the sat/1
residuals, posts them again, asks CLP(B) for the BDD representation, and then shows the BDD. This overhead is often perfectly acceptable, because if CLP(B) has managed to distill a reasonable sat/1
representation of the BDD, then it will also happily process it again.
So, normally, the default sat/1
goals are OK and even preferred. In precisely the slow cases though, we need to rely on the BDD representation throughout, and do not try a single projection to sat/1
goals.
I see. Well, SWISH has, due to its multi-user and threading aspects, some limitations, but also provides some opportunities. What about this (for swish)
- Set clpb's flag globally to bdd in the swish initialization
- Render the bdd using graphviz
- Add a secondary renderer that stores the bdd and, when selected through the render menu, performs a callback to get the sat/1 representation.
This provides a nice picture by default and the expensive-to-compute sat/1 on request.
Note that we can also present a single renderer with which we register the BDD and which just provides an indication of the residual and allows the user to select a rendering (or not if s/he is not interested). We can also spend a short time in the renderer to compute the sat/1 representation and display the result if cheap and provide a link/button otherwise.
Is there any way to make the clpb_residuals
flag work like on the normal Prolog toplevel also in SWISH? If that is possible, I would strongly prefer this over other workarounds. Here are a few good reasons:
-
sat/1
residuals are typically preferable for users, because they often simplify the original constraints in such a way that new information is made explicit and very easily readable for users. Example: In Knights and Knaves, which even ships with SWISH, querying?- example_knights(5, [A,B,C]).
yieldssat(A =\= B)
as one of the residual goals. However, the textual BDD representation does not really make clear thatA
andB
must be different in this example. The graphviz figure is slightly better, but overall, thesat/1
goal is best, like in many other examples. For this reason alone already, we cannot setclpb_residuals
tobdd
globally by default. -
sat/1
constraints are therefore the default residual goals in normal SWI usage. Emitting a BDD representation in SWISH would unexpectedly differ from the default SWI behaviour. - Setting
clpb_residuals
tobdd
in SWISH in this way would introduce a strong dependency on thebdd
renderer being always enabled. However, this will typically not be the case! Most users who try out CLP(B) constraints in SWISH will likely overlook the renderer. Alas, without the renderer, there's then also no way to obtainsat/1
residuals instead of BDDs. - Going from a BDD to a SAT representation would require a new interface predicate in
library(clpb)
and raises some semantic questions about what to do ifsat/1
constraints are mixed with direct BDD specifications. On the other hand, going from asat/1
residual to a BDD is straight-forward and works already.
Is there any way to let users set the clpb_residual
flag in SWISH programs, so that SWISH behaves more like the normal Prolog toplevel? I notice for example that setting clpfd_monotonic
to true
works as expected in SWISH and affects CLP(FD) programs in the intended way. Allowing users to set such flags specific to their own programs is also likely to become even more important in the future, for example in connection with double_quotes
set to chars
.
Is there any way to make the clpb_residuals flag work like on the normal Prolog toplevel also in SWISH?
As I tried to explain, this is hard. Pengines are about computing answers. They transfer the answer, in this case as a variable with attributes to the client. The rendering of answers in a human digestible way is part of SWISH. It happens at the client side (with respect to the Pengine; it still runs on the server process), which cannot be aware of flags in the server as there are no provisions to talk to the server and in the normal scenario the server is gone if there are no more solutions.
So, setting Prolog flags to influence rendering is a no-go. It would require a different interaction between client and Pengine which might be interesting for some SWISH UI scenarios, but would break (or at least ask for more kludges) for the scenario where a SWISH server is used as a generic API to a data collection. That is a pretty important use case that currently pays my bills.
So, I fear the realistic way out is a residual representation that is fixed (at least in SWISH) and allows to do the renderer whatever it needs to do. Note that it is not a problem to have the clpb renderer always loaded as long as you use terms that are sufficiently unique. You could make the clpb residual generation hookable instead of using a flag, so the renderer module can create the term it wants to see.
An alternative might be that the answer is defined not to be just a set of variable bindings using general Prolog values (including constraints), but is in general the combination of a set of variable bindings without attributes and residual goals. That would not break the overall design, but I fear it will require incompatible changes to the Pengine API. I'll need to think about that route.
I think the last route is best, also for future uses. Please do think about this. I will also think about the extension approach. Currently, I have severe doubts about it. I only want to briefly summarize what I need and expect from the rendering interface and the interaction between renderers and constraint libraries, not as a completely stringent argument, but just a sketch of the things that are involved already in the CLP(B) case, and possibly even more so in future applications. For the sake of concreteness, I write this with the focus on CLP(B):
- There is a clear preference of residual goals:
sat/1
goals. Reason: This is already part of the CLP(B) interface, so such residual goals can be pasted back on the toplevel without problems. - In some cases, obtaining the
sat/1
representation is prohibitively hard. - We therefore have a second representation of CLP(B) constraints: Binary Decision Diagrams (BDDs), to be used as a last resort or to satisfy the users' curiosity.
- In general, seeing just the BDD as a Prolog term will not tell users what they want. Therefore, if emitting BDDs is the default, then the renderer must also be always enabled.
- BDDs are Prolog terms of the form
clpb:'$clpb_bdd'(...)
. This is sufficiently different from any conceivable other occurring Prolog term to let the renderer process it every time such a term occurs, and to enable the renderer by default. - Always enabling the renderer though is a severe accessibility handicap for blind users (for example). In addition, it differs completely from the way that all other renderers work (using the
:- use_rendering/1
directive). - Further, changing the default residuals to BDDs makes SWISH completely different from the normal toplevel, complicating teaching Prolog using both systems.
- Still, suppose we always enable the BDD residuals and hence the BDD renderer in SWISH. The BDD can be extremely large, the SVG can crash graphviz, the client, or both. Since it is always on, there is no way to disable the renderer, although the textual representation of the BDD may very well be processable and could have been displayed to users! So this implies that there should also be a way to turn off renderers, which previously wasn't needed.
- Suppose we nevertheless stick to this decision, always enable the renderer, and always use the BDD representation, even though I think the above already makes clear that this is not a good idea for several reasons.
- Suppose further that the renderer hasn't crashed graphviz or the client, and users now see the graph. In many if not most cases, they actually want the
sat/1
representation instead! So, the renderer provides a way to translate BDDs tosat/1
. This is the job thatlibrary(clpb)
knows how to do in principle, so the renderer can ask the library to do it. - However, BDDs make sense as output, but not as input for CLP(B). Therefore, there is currently no interface predicate in CLP(B) that accepts BDDs.
- If we provide a predicate
clpb:'$clpb_bdd'/1
, then BDDs could in principle even be processed by CLP(B) as input, preserving the important property that all emitted goals can really be pasted back. But the primary interface of CLP(B) issat/1
goals, so it is somewhat dubious to introduce a separate interface predicate for BDDs. This comes with some semantic questions I need to think through. - My preference is to keep renderers nicely separated from libraries. Adding additional interface predicates just for the sake of renderers feels like a kludge. I am willing to do this for CLP(B) as an isolated case, but other libraries well run into the same issue, so this is something well worth thinking about and solving now that we have CLP(B) as a test case that exhibits many of the issues we need to address.
- The way we communicate with constraint solvers is residual goals that can be pasted back.
- Any reported binding like
Var = Value
is, in principle, the same as any other residual goal. So, everything the toplevel emits (in pure programs) can be uniformly treated, be it variable binding or any other constraint likesat/1
goals, CLP(FD) goals,dif/2
and what not. - For this reason, I encourage the way you propose to handle this in the last sentences: Generalizing the Pengine API to provide what is actually needed: Access to residual goals.
- That's not all though: Obtaining the residual goals is exactly the hard part in the case of CLP(B).
- The question therefore somehow remains: How to circumvent the hard BDD ->
sat/1
projection in a controlled way, i.e., such thatsat/1
is the default, but BDDs are obtained on demand if necessary? - I also need to think more about this ;-)