[comp.lang.prolog] '->' operator

bradley@cs.utexas.edu (Bradley L. Richards) (01/04/91)

I have a (probably silly) question regarding the '->' operator in Quintus.
Suppose I say

   Condition -> Predicate

If the condition is true, the predicate will execute.  Fine.

If the condition is true and the predicate fails, the whole conditional fails.
  This makes sense since logically (true -> false) is false.

If the condition is true and the predicate is true, the whole thing succeeds.
  This makes sense since (true -> true) is true.

BUT if the conditional is false, the ugly little beastie fails--this doesn't
  make sense since logically (false -> anything) is *true*.

Why is this implemented the way it is?

Thanks,
Bradley
bradley@cs.utexas.edu

mcovingt@athena.cs.uga.edu (Michael A. Covington) (01/04/91)

In article <291@valverde.cs.utexas.edu> bradley@cs.utexas.edu (Bradley L. Richards) writes:
>I have a (probably silly) question regarding the '->' operator in Quintus.
>Suppose I say
>
>   Condition -> Predicate
>
>If the condition is true, the predicate will execute.  Fine.
>
>If the condition is true and the predicate fails, the whole conditional fails.
>  This makes sense since logically (true -> false) is false.
>
>If the condition is true and the predicate is true, the whole thing succeeds.
>  This makes sense since (true -> true) is true.
>
>BUT if the conditional is false, the ugly little beastie fails--this doesn't
>  make sense since logically (false -> anything) is *true*.
>
>Why is this implemented the way it is?
>
>Thanks,
>Bradley
>bradley@cs.utexas.edu

Generally, "false -> anything" is not true in Prolog. Prolog is not quite
the same as classical logic. The main differences are (1) limitations on the
form of formulas, and (2) absence of explicit negation (in Prolog, "not P"
means "unable to prove P").
  
  Further, the -> operator is not intended to be an encoding of anything
  in classical logic. It is a Pascal-like, *procedural* if-then-else
  construct, designed to make it easier to express algorithms.
  The equivalent of classical logic "implies" is :- .

bradley@cs.utexas.edu (Bradley L. Richards) (01/04/91)

In article <1991Jan4.030918.24996@athena.cs.uga.edu> mcovingt@athena.cs.uga.edu (Michael A. Covington) writes:
>  Further, the -> operator is not intended to be an encoding of anything
>  in classical logic. It is a Pascal-like, *procedural* if-then-else
>  construct, designed to make it easier to express algorithms.
>  The equivalent of classical logic "implies" is :- .

Ah, but if '->' is intended to be an implementation of the procedural
if-then-else (or, in the case I'm concerned with, if-then) then it
should still succeed if the condition is false.  After all, procedurally
execution will continue following an if statement whether or not the
condition in the if was true.

So either under the logical interpretation or under the procedural one
it seems to me that the Quintus '->' works improperly.

Bradley

-------------------------------------------------------------------------------
 Bradley L. Richards             "The abandonment of formal mathematics
 bradley@cs.utexas.edu           is an extremely popular thing to do in
 uucp:  cs.utexas.edu!bradley    computer science."
                                                    Dr. Robert Boyer, NACLP-90
-------------------------------------------------------------------------------

mcovingt@athena.cs.uga.edu (Michael A. Covington) (01/04/91)

In article <16491@cs.utexas.edu> bradley@cs.utexas.edu (Bradley L. Richards) writes:
>
>Ah, but if '->' is intended to be an implementation of the procedural
>if-then-else (or, in the case I'm concerned with, if-then) then it
>should still succeed if the condition is false.  After all, procedurally
>execution will continue following an if statement whether or not the
>condition in the if was true.

   Ah. I had not quite realized that it didn't. So (p -> q) fails if 
   p fails?
   
>So either under the logical interpretation or under the procedural one
>it seems to me that the Quintus '->' works improperly.
>
   I hope R. A. O'Keefe (the most vocal defender of "->"; he may
   even have invented it) will join this discussion.
   

fuchs@ifi.unizh.ch (01/04/91)

In article <1991Jan4.061142.26941@athena.cs.uga.edu> mcovingt@athena.cs.uga.edu (Michael A. Covington) writes:
>In article <16491@cs.utexas.edu> bradley@cs.utexas.edu (Bradley L. Richards) writes:
>>
>>Ah, but if '->' is intended to be an implementation of the procedural
>>if-then-else (or, in the case I'm concerned with, if-then) then it
>>should still succeed if the condition is false.  After all, procedurally
>>execution will continue following an if statement whether or not the
>>condition in the if was true.
>
>   Ah. I had not quite realized that it didn't. So (p -> q) fails if 
>   p fails?
>   
>>So either under the logical interpretation or under the procedural one
>>it seems to me that the Quintus '->' works improperly.
>>
>   I hope R. A. O'Keefe (the most vocal defender of "->"; he may
>   even have invented it) will join this discussion.
>   

I will not anticipate Richard O'Keefe's answer, but P -> Q works as if
implemented as P, !, Q.

   --- nef

kilian@seas.gwu.edu (Jens Kilian) (01/04/91)

As far as I know, the '->' operator is implemented as a 'local cut'. Thus,

	P -> Q; R

is equivalent to 

	P, !, Q; R

provided that the scope of the cut is limited to the disjunction. According
to the Quintus manual,  (P -> Q) is equivalent to (P -> Q; false), which
explains why (P -> Q) fails if P fails. The only reason I can imagine is
that (P -> Q; false) need not create a choice point, while (P -> Q; true)
must create one.
--
Internet: kilian@seas.gwu.edu		SnailMail: 4715 MacArthur Blvd.
(I don't know any other addresses ...)		   Washington, DC 20007
"Sie hawwe-mer so e bekannt Physionomie, ich mahn, ich misst Ihne kenne.
 Sinn-Se net, um Vergebung, der Herr Assesser Ranft ?"

dan@sics.se (Dan Sahlin) (01/10/91)

Jeff Schultz wrote:

>I find the definition of (C -> T) as (once(C), T) much less useful in
>practice than the if-like one, but there's no question that it's the
>standard behaviour.  Sad, really.

I agree, and would add that not only is the semantics bad, but also the
syntax of if-then-else, especially if you do program transformations.

For instance, "A;(B;C)" is not equivalent to "(A;B);C" in Prolog, due to the
poor syntax of if-then-else. Let A be "(Test->Then)" and you see why.

Another example, "true,D" is not always the same as "D", if "D" is
"(Test->Then)".  The expression "(true,(Test->Then));E" is not the same as
"(Test->Then);E".

It really becomes complicated if you have a clause of the form
	p(G,X) :- G; X=2.
So what happens if you call "p((true->X=1),X)"?

Instead just getting X=1, you also get X=2 on backtracking, as the clause
when read in is first converted into
	p(G,X) :- call(G); X=2.

On the other hand, not all meta-goals G are converted into call(G), as in the
clause
	p2(G,X) :- call((G; X=2)).
The call "p2((true->X=1),X)" will only return the answer X=1.

The above examples are run in compiled and interpreted SICStus Prolog, but
many other Prolog systems show the same behavior.  If I am correctly
informed, the forthcoming Prolog standard will keep this syntax and
semantics of if-then-else.

	/Dan Sahlin

roland@sics.se (Roland Karlsson) (01/10/91)

Incredible.  I am amazed.  try this four "equivalent" predicates.

p1   :- ((/*true,*/(true->write(1)      )) ; write(2)), fail.
p12  :- ((  true,  (true->write(1)      )) ; write(2)), fail.
p12a :- ((/*true,*/(true->write(1);false)) ; write(2)), fail.
p12b :- ((  true,  (true->write(1);false)) ; write(2)), fail.

--
Roland Karlsson
SICS, PO Box 1263, S-164 28 KISTA, SWEDEN	Internet: roland@sics.se
Tel: +46 8 752 15 40	Ttx: 812 61 54 SICS S	Fax: +46 8 751 72 30

bimbart@kulcs.cs.kuleuven.ac.be (Bart Demoen) (01/14/91)

Thomas Sjoeland <1991Jan11.170214.3756@sics.se> writes:

> Should we take it (->;) out ?

In the course of the standardisation process, it has been in and out and very
recently in again.

It was out before, because of its syntax, because of different behaviour in
different systems and because taking it out at some moment, was the right
compromise to keep the standardisation process going.

It was put back in, because most Prolog systems have it, because it would break
too many programs by taking it out, because the differences between actual
implementations were less important than previously thought and because the most
recent meeting was the right moment to put it back in. (The last meeting was
memorable for other decisions as well, e.g. about modules.)

So, sorry for those disappointed: if-then-else is IN right now and in the
DEC-10 form and with DEC-10 meaning - mostly.

> The standard committee should think hard about these things.

It has. And not all problems are solved with if-then-else. Perhaps people want to
give their opinion about the following:

	should ! in the condition be allowed ? (QP doesn't - since when ?)
	if yes, what should be its scope ?
			(local to condition or up to head included ?)

	should ?- X = (true -> write(1)) , call((X ; write(2))) . have the
	same answer as ?- X = (true -> write(1)) , (X ; write(2)) .
	and as ?- true -> write(1) ; write(2) .


> Why not sort out the overloading of commas and the list syntax while you're at it ?

The standard committee has been critisized a lot for designing a new language
instead of standardising an old one, and that's why certain things can't be
done, however much we can regret this.


Bart Demoen

matsc@sics.se (Mats Carlsson) (01/14/91)

In article <1991Jan11.204339.25431@athena.cs.uga.edu> mcovingt@athena.cs.uga.edu (Michael A. Covington) writes:
   My recollection is that the proposed standard does not include if-then-else.

On the contrary, the forthcoming ISO standard will include
if-then-else with its Edinburgh syntax.  The people involved in
ISO/JTC1/SC22/WG17 (including me) are aware of the problems with '->'
and ';', but I am convinced that trying to invent something different
at this stage would be a big mistake.
--
Mats Carlsson
SICS, PO Box 1263, S-164 28  KISTA, Sweden    Internet: matsc@sics.se
Tel: +46 8 7521543      Ttx: 812 61 54 SICS S      Fax: +46 8 7517230

felkl@aste16.Berkeley.EDU (Feliks Kluzniak) (01/15/91)

In article <1471@n_kulcs.cs.kuleuven.ac.be>,
bimbart@kulcs.cs.kuleuven.ac.be (Bart Demoen) writes:

|> The standard committee has been critisized a lot for designing a new
language
|> instead of standardising an old one, and that's why certain things can't be
|> done, however much we can regret this.

This is interesting. Does it mean that the committee has not, after all,
designed a new language?  If it hasn't, the criticism was uncalled for;
if it has, I can't see the logic.

-- F.K.

wachtel@canon.co.uk (Tom Wachtel) (01/17/91)

felkl@aste16.Berkeley.EDU (Feliks Kluzniak) writes:

>In article <1471@n_kulcs.cs.kuleuven.ac.be>,
>bimbart@kulcs.cs.kuleuven.ac.be (Bart Demoen) writes:

>|> The standard committee has been critisized a lot for designing a new
>|> language instead of standardising an old one, and that's why certain 
>|> things can't be done, however much we can regret this.

>This is interesting. Does it mean that the committee has not, after all,
>designed a new language?  If it hasn't, the criticism was uncalled for;
>if it has, I can't see the logic.

But, I suppose, if it had, it would not have been, and if it hadn't
seemed like it might have done, it would also not have been, and since
it was, it didn't, and otherwise there would have been fewer auxiliary
verbs in this sentence.

Tom Wachtel (wachtel@canon.co.uk)

lee@munnari.oz.au (Lee Naish) (01/21/91)

In article <1471@n_kulcs.cs.kuleuven.ac.be> bimbart@kulcs.cs.kuleuven.ac.be (Bart Demoen) writes:
> Perhaps people want to give their opinion about the following:

Ok, here is my 2c worth.
>	should ! in the condition be allowed ?
No, its just too horrible to contemplate.

>	should 1?- X = (true -> write(1)) , call((X ; write(2))) . have the
>	same answer as 2?- X = (true -> write(1)) , (X ; write(2)) .
No.
>	and as 3?- true -> write(1) ; write(2) .
Yes.

I think a variable X in the place of a goal should be the same as
call(X) (it would be even better to force programmers to write
call explicitly; but that would break quite a few programs).  Nothing
inside call should be fiddled with/interpreted until runtime when the
variable bindings are known.  At that time the argument of call should
be treated like a clause body with its own scope for the purpose of
cuts.

Thus, the second goal above is equivalent to
	?- X = (true -> write(1)) , (call(X) ; write(2)).
and the -> cannot be affected by the ;.  With the first goal, the ; is
not interpreted as a disjunction initially because its inside call.  At
runtime, X is instantiated to -> and ; is interpreted as "else".
With the following goal
	?- X = (true -> write(1)), call((Y = X, (Y ; write(2)))).
when call is executed, Y is uninstantiated, so the second occurrence
should have an extra call wrapped around it (like the first goal
above).

Much of the complexity stems from language designers trading
interpretation and compilation simplicity for syntax (eg allowing X
instead of call(X) and using (P->Q;R) instead of if(P,Q,R)).  This tends
continues when explicit quantifiers are introduced.  The syntax is much
nicer if quantified variables are listed explicitly but interpretation
is simpler if all unquantified variables are given explicitly.

One solution to this dilemma is to have a well defined translation from
the user level language to an intermediate language which is suited to
interpretation and other manipulation (with if/3, explicit unquantified
variables and maybe without normal cut).  The user level language can be
considered a shorthand for this language.  More efficient variants of call,
clause etc which use the intermediate language can then be defined.  Its
easy to keep enough information for a reasonable version of listing as well.

	lee

Ray.Nickson@comp.vuw.ac.nz (Ray Nickson) (01/22/91)

In article <6483@munnari.oz.au> lee@munnari.oz.au (Lee Naish) writes:

   (it would be even better to force programmers to write
   call explicitly; but that would break quite a few programs)

Would it break too many programs?  More than other proposals in the
standard would?  Lots of complexity in the draft draft standard I
looked at (WG17 N64) arose from allowing this feature; I'd prefer it
to be dropped.  For one thing, programmers using metacalls should at
least be aware that they are no longer writing logic; when call/1 is
not written explicitly, this may not be obvious.

My opinions on the if-then-else issue: (I use ->/2 and ;/2 a lot,
although I'd prefer a more sensible syntax).

In article <1471@n_kulcs.cs.kuleuven.ac.be> bimbart@kulcs.cs.kuleuven.ac.be (Bart Demoen) writes:
   > Perhaps people want to give their opinion about the following:

   >	should ! in the condition be allowed ?
Yes; I see no reason why not (though I have never implemented such a
thing).  The cut should apply just to the condition.  In fact, I'd
like implementations (optionally) give a warning on potential
indeterminacy in the condition, then (Cond -> Then ; Else) could be
given up in favour of if((Cond,!), Then, Else), where if/3 explores
all solutions to Cond (as in SICStus).

   >	should 1?- X = (true -> write(1)) , call((X ; write(2))) . have the
   >	same answer as 2?- X = (true -> write(1)) , (X ; write(2)) .
   >	and as 3?- true -> write(1) ; write(2) .  
If implicit metacalls are allowed, it seems more natural to treat X as
if its binding at call time were explictly written in place; this
would make X transparent to cut, and the answer to the above questions
yes.  This makes X different from call(X), and like
transparent_call(X), although I've never needed a transparent call
anyway.  These appears to be what SICStus does, despite the manual
saying X and call(X) are identical.  Does someone have an example of
where transparent call is actually useful?

ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe) (01/31/91)

In article <NICKSON.91Jan21193710@circa.comp.vuw.ac.nz>, Ray.Nickson@comp.vuw.ac.nz (Ray Nickson) writes:
> Would [dropping implicit "call"] it break too many programs?
> More than other proposals in the standard would?

There isn't any reason whatsoever why leaving implicit "call" out of the
standard should break ANY programs.  It could remain as a "common extension",
just as P(X,Y,Z) as a shorthand for call(P, X, Y, Z) is a not-altogether-
unheard-of extension.  (The public-domain version of the DEC-10 Prolog parser
quietly converts such terms.  In practice it was found that such terms were
almost always mistakes, so the misfeature was dropped from Quintus Prolog.)
What would break programs would be if the standard defined variables occuring
where goals are expected to do something *else*.  In particular, insisting
that such "goals" be rejected at compilation or assertion time, that would
break programs.  My suggestion, for what it is worth, would be for the
standard to leave the effect of goals that are not callable terms
implementation defined.  That way, call(X) could and should be opaque, as
at present, and an implementor whose "..., X, ..." is currently equivalent
to the surpassingly bizarre transparent_call(X) wouldn't need to change one
little thing.  If the standard said that "the behaviour of a non-callable
term X as a goal is not defined by this standard, although it is common
practice for such goals to behave somewhat like call(X)", then programs using
the feature would be no less portable than they are now.

> Does someone have an example of where transparent call is actually useful?

I second this question.  I have never come across any programming situation
where transparent_call/1 (as opposed to call/1) would have been useful.  It
is worth noting that as long as if->then;else is transparent to cuts
(so that you can have "conditional cuts" (X=:=0 -> ! ; true)) it's fairly
easy to obtain the effect of transparent_call/1.  Use the interpreter in
"on the treatment of cuts in Prolog source-level tools", and do
	p(...) :-
		q(...),
		interpret(X, HadCut, AfterCut),
		( HadCut == true -> !, call(AfterCut) ; true ),
		r(...).   %         ^ this cut has p as parent
so the implementation of transparent_call/1 is trivial.  (It could be added
to Quintus Prolog in a couple of days at most.  Documentation would be the
hardest part, in the absence of any sensible examples of its use.)
-- 
The Marxists have merely _interpreted_ Marxism in various ways;
the point, however, is to _change_ it.		-- R. Hochhuth.