SWI-Prolog / roadmap

Discuss future development
20 stars 3 forks source link

Attribute evaluation Order to be respected by individual attributes #52

Open TeamSPoon opened 6 years ago

TeamSPoon commented 6 years ago

Attribute order is important:

% EXHIBIT 1
?-  freeze(X,writeln('I planning on failing if value is "foo"': X)), dif(X,foo),     X=foo.
I planning on failing if value is "foo":foo
false.
% EXHIBIT 2
?- dif(X,foo), freeze(X,writeln('I better not see the value is "foo"': X)),      X=foo.
false.

The above two example work allowing certain types of programming to be possible.

However, the various actors in this are not playing nice when it comes to working together. For instance we would expect this code:

% EXHIBIT 3
?- freeze(X,writeln('I planning on failing if value is "foo"': value=X)), 
    dif(X,foo), 
    freeze(X,writeln('I better not see the value is "foo"': value=X)),
    X = foo.
I planning on failing if value is "foo":value=foo
I better not see the value is "foo":value=foo
false.

to not print

   'I better not see the value is "foo"': value = foo. `

And it erroneously did due to the fact that freeze/2 is combining the two calls together before dif/2.
We know this problem and normally work around it by implementing our own.

I'm sure that some would like to argue that we should never see either print statements?

Sample argument:

"dif/2 has a strong meaning!"

My rebuttal: "In other words are we saying that we cannot compose constraint stronger than dif/2? So are you saying my EXHIBIT 1 shows that the SWI implementation is wrong? If so, someone should be document someplace a "standard order" in which all attributes should be evaluated (that shows dif/2 being first). Also why then is dif/2 not placing itself first via put_attrs/2 ?"

freeze/2 is not the only bad actor here... even dif/2 is naughty:

EXHIBIT 4
?- dif(X,foo), 
    freeze(X,writeln('I hope i see this "bar" before I fail': value=X)),
    dif(X,bar),
    X = bar.
false.

Erroneously failed to print:

I hope I see this "bar" before I fail': value=bar
false.

Sample argument:

Several experts time and great thoughtfulness have contributed to the code of dif/2and updated it several times. Cant, we celebrate one of the golden periods finally everyone but you think it is correct?

Rebuttal: So why then do we bother caring about the order in which we place attributes?

In fact, it even purposely is designed to merge attributes!

Yes, for handing: dif(X,foo),dif(X,bar),dif(X,baz),

But not for

?- dif(X,foo),dif(X,bar),dif(X,baz),..other delays...,dif(X,bang), X=bang.

Anyways, if what I am saying is agreeable

there are several ideas to choose from / and suggest better:

Solution 1

Placing dif/2, when/2, freeze/2 all in the same codebase as when/2.

Though we need update $when to handle unification to call a hook when two attvars unify (as dif/2 needs). not sure that'?='(X,Y)covers that.

Solution 2

The most popular solutions it to make these guys on the second call:

freeze(X,G):-  
    gensym('$frozen',Module),
    asserta(Module:attr_unify_hook(G0,Value):-(nonvar(Value)->call(G0);true)),
    asserta(Module:attrbute_goals(Var,[freeze(Var,G0)],T):-get_attr(Var,Module,G0)),
    put_attr(X,Module,G),...

When/where do we clean up the assert database?

Solution 3

change att/3 to allow duplicated attributes. (worse idea yet?) or..

Allow attribute list one special attribute called '$goal' that is allowed to be duplicated in which when/dif/2 and everyone may insert into the attribute/wakeup list. This one attribute each time it is encountered (between attributes it is merely called)

dif(X,Y):- X\==Y,
    (var(X)->append_var_wakeup_goals(X,Value,dif:attr_unify_hook(X,Value));true),
    (var(Y)->append_var_wakeup_goals(Y,Value,dif:attr_unify_hook(Y,Value));true).
freeze(X,G):-  
    append_var_wakeup_goals(X,Value,(nonvar(Value)->call(G);true))).

Heh, actually makes frozen_goals meaningful, the downside is that goals are not as attached to attributes as we'd like.

I had suggested this be dispersed this over multiple $goals mainly to make sure they happened correctly around the attr_unify_hooked/2 modules.

Actually, let's look at Solution 1 again:

Solution 4

Combining Solution 1 and 3

append_var_wakeup_goals/3 be placed in $when space.

This also could not make null hooks like '$var_info':attr_unfy_hooks(_,_). optional.

That instead of people use: append_var_wakeup_goals(-Var,-Value,+Goal)s that are appended to the residual goals.

This allows the system perhaps later on to do things like compiling the goals

Other thoughts

I am sure more refined solutions than the 4 above would also be possible.

I mixed in I/O in the Exhibits, not a selling point, it is just easier to understand those. The same problem happens the same between when/2 and freeze/2 and dif/2 and when/2. And with anyone using attvar_unify_hook/2 with any one of those library helpers. You can imagine this introduced very subtle bugs that no one could track changing to a different callback hook especially if they used all_different/1 or dif/2 with constraint solver code. Like dif/2 kicking in after their hook was called yet in the past it was happening _before. On the other hand, if the library created hooks order are more correct as proposed in this document, it could even more of such subtleties even now.