How can I simulate a soft cut in Prolog?
Asked Answered
E

4

5

How can I simulate a soft cut I *-> T; E in ISO Prolog? I has side effects, so I can not call it multiple times.

Except for the last requirement, I think the following definition works:

if_(I, T, E) :-
    not(not(I)) ->
    call((I, T));
    call((not(I), E)).

(I'm actually using XSB prolog; a solution for XSB would be useful for me too.)

Entremets answered 15/11, 2016 at 21:58 Comment(2)
Rather use if/3 for this, like SICStus does. Also, why do you need this construct? Note that you do not get monotonicity with it. It has similar flaws like Prolog style negation has.Plagiarize
I wonder whether it is not possible to use XSB's tabling functionality to do this.Danialah
P
5

Yes, we can implement this in ISO Prolog and even in XSB, but not very efficiently. To make this efficient, you would need some "selective cut". Further, XSB does not implement ISO conforming integers so the overflow must be handled separately.

:- dynamic(if_counter/1).

if_counter(0).

:- dynamic(no_if_answer/1).
if(If_0, Then_0, Else_0) :-
   once(if_counter(Id)),
   Idx is Id+1,
   (  Idx > Id -> true
   ;  throw(error(representation_error(max_integer),
               'XSB misses ISO conforming integers'))
   ),
   retractall(if_counter(_)),
   asserta(if_counter(Idx)),
   asserta(no_if_answer(Id)),
   (  If_0,
      retractall(no_if_answer(Id)),
      Then_0
   ;  retract(no_if_answer(Id)) ->
      Else_0
   ).

The major source of inefficiency is that for a determinate condition If_0, there is still a choice point left. It is thinkable next to unthinkable that an implementation could conclude that retract(no_if_answer(Id)) will always fail, once retractall(no_if_answer(Id)) has been executed, but I doubt that implementers will invest in such optimizations. EDIT: The reason why this seems highly improbable is that an implementation would have to guarantee that the numbers asserted always go up.

Note that soft cut produces incompleteness in the same way the cut does. Consider:

| ?- if(X = a, T = equal, T = not_equal).

X = a
T = equal;

no

This clearly misses an answer! To see why, take X = b:

| ?- X = b, if(X = a, T = equal, T = not_equal).

X = b
T = not_equal;

no
| ?- if(X = a, T = equal, T = not_equal), X = b.

no % bad!!

Conjunction should be commutative (modulo non-termination, errors, side-effects).

If you are interested in declaratively sound conditionals that are also very efficient and often faster than their impure counterparts, consider if_/3. See library(reif) for SICStus which gives all correct answers:

| ?- if_(X = a, T = equal, T = not_equal).
X = a,
T = equal ? ;
T = not_equal,
prolog:dif(X,a) ? ;
no
Plagiarize answered 16/11, 2016 at 19:25 Comment(1)
If the soft cut arguments don't leave a choice point, the soft cut should also not leave a choice point. See SWI and Jekejeke behavior.Sarthe
D
4

Ok, let's get creative... You essentially need a way to remember (across backtracking) that the If-condition had at least one solution. Dynamic predicates are a no-no for me, but are there any alternatives? Well, ISO-Prolog defines one kind of anonymous object, the stream-term, which could be (ab)used to implement the non-backtrackable flag in this rather elegant way:

if(If, Then, Else) :-
    open(., read, S),
    (
        If,
        close(S, [force(true)]),
        Then
    ;
        catch(close(S), error(existence_error(stream,_),_), fail),   % fail if already closed
        Else
    ).

We close the stream to indicate that If had a solution, and this is then detected by the close-attempt in the else branch. This works perfectly and leak-free in a system like ECLiPSe. However, many systems (including XSB) re-use the identifiers of closed streams (which is not forbidden by ISO), making this solution non-portable.

But wait, streams have a position property, which can be set, and which retains its value across backtracking! Using this trick, the following works on XSB:

if(If, Then, Else) :-
    % open('ReadableAndNonemptyFile', read, S),      % general ISO
    open(atom(a), read, S),                          % XSB (needs no file)
    stream_property(S, position(Zero)),
    get_char(S, _),
    (
        catch(If, Ball, (close(S),throw(Ball))),
        set_stream_position(S, Zero),
        Then

    ; stream_property(S, position(Zero)) ->
        close(S),
        fail
    ;
        close(S),
        Else
    ).

Sadly, the open(atom(...),...) feature is XSB-specific, for strict ISO-Prolog you need a dummy file...

Danialah answered 17/11, 2016 at 15:36 Comment(4)
This is a really clever solution. When I dropped it into my application, it tried to open 'a' twice at the same time though and failed. I use if recursively, which is what I imagine the problem is. Is there any way to open a fresh stream for each invocation of if?Entremets
The former produces permission_error(open,file,.) in XSB, a system_error in SICStus, but GNU accepts this, but only 1023 times...Plagiarize
@EdMcMan: it does open a fresh stream on every invocation, but it seems XSB has a small limit (4 in my XSB 3.7) on open atom-streams. If you open a file instead, the problem goes away.Danialah
The latter works only for 4 simultaneous instances in XSB. Then, open(atom(a), read, S). is an error.Plagiarize
S
0

Your definition doesn't implement soft-cut semantics: when the test succeed, you can backtrack into it. This is useful control construct (I use it e.g. to implement coinduction in Logtalk) but unfortunately cannot be implemented in a portable way at the Prolog level and certainly within the restrictions of the ISO Prolog standard. Good news is that a growing number of Prolog systems implement this control construct. These include, in no particular order, SWI-Prolog, YAP, SICStus Prolog, GNU Prolog, CxProlog, ECLiPSe, Jekejeke Prolog, and Ciao. Note, however, that while some systems use the *->/2 operator, a few (SICStus Prolog and Ciao) use a if/3 predicate (YAP have both). Also, semantics vary in corner cases (the Logtalk distribution includes a Prolog conformance suite that also checks the *->/2 variant).

Shurlocke answered 16/11, 2016 at 2:56 Comment(1)
Are there more use cases of (*->/2) except coinduction?Sarthe
S
0

The problem is, that the soft cut should be fairly smart, it shouldn't leave a choice point when its arguments don't leave a choice point.

No choice point in SWI-Prolog:

   Welcome to SWI-Prolog (threaded, 64 bits, version 8.1.4)

   ?- X=1 *-> Y=1; true.
   X = Y, Y = 1.
   ?- 

No choice point in Jekejeke Prolog:

   Jekejeke Prolog 3, Runtime Library 1.3.6

   ?- X=1 *-> Y=1; true.
   X = 1,
   Y = 1
   ?- 

So far none of the admittedly creative solutions here archive that, so none of them can replace a native implementation usefully.

Jekejeke Prolog does a determinism check, and then removes the disjunction choice point. Otherwise, it marks the disjunction choice point. From module "logic":

:- set_predicate_property(;/2, sys_nobarrier).
A *-> B; C :- sys_local_cut, sys_soft_cond(A, B, C).

:- set_predicate_property(sys_soft_cond/3, sys_nobarrier).
sys_soft_cond(A, B, _) :- sys_safe(A), sys_soft_local_cut, B.                        
sys_soft_cond(_, _, C) :- C. 
Sarthe answered 30/3, 2019 at 21:16 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.