[comp.lang.prolog] WG17 against Sterling and Shapiro

ok@cs.mu.oz.au (Richard O'Keefe) (11/08/89)

		WG17 against Sterling and Shapiro
		--------- an evaluation ---------

    I have complained, for several years now, that the BSI committee and
now WG17 do not seem to regard other people's work as important.  I have
had in mind other people's programs,but that's not the only kind of work
that deserves to be protected.  A particularly important class of work I
believe should be protected is Prolog textbooks, not that there are many
of *those* that I like.  With respect to textbooks,there are three kinds
of people who will be hurt by a standard which differs too much from the
descriptions in the books:
	(a) the publishers, whose current offerings will be diminished
	    in value
	(b) the authors, who will either have to produce new editions
	    of their works, or see their books decline in the market as
	    no longer relevant (e.g. John Stobo's book, which was to
	    a large extent based on the standard as it stood when he
	    wrote, now no longer reflects *either* the standard *or*
	    an existing Prolog)
	(c) the purchasers, who bought books which _did_ describe
	    Common Prolog, but who will have to purchase additional
	    books if they want something that describes the standard.

I wonder whether it would somehow be possible for the publishers (such
as Springer-Verlag, MIT Press, Prentice-Hall, and one or to others) to
have a representative on the ISO committee -- it seems to me that they
have done more for the Prolog community than the committee have, and
definitely deserve to have their interests represented.  In this case
their interests (continued markets for their books) coincide with their
authors' interests and ours.

    To demonstrate that there is a real threat to existing worthwhile
books, I thought it would be appropriate to look at Appendix B of
Sterling and Shapiro's "The Art of Prolog".  It has to be admitted that
some of the predicates they describe there are specific to Wisdom Prolog.
In the table which follows, I've labelled such predicates "private",
others are labelled "common".

GRAMMAR RULES		common		DELETED

atom/1			common		present (used to be broken, ok now)
integer/1		common		present
atomic/1		common		present
constant/1		private
functor/3		common		present
arg/3			common		modified
var/1			common		present
nonvar/1		common		present

    Note:  the change to arg/3 is that in arg(N,Term,Arg), if N < 1 or
    N > arity(Term) an error MUST be signalled instead of the former
    quiet failure.  This contradicts explicit statements in S&S, and
    more importantly it is incompatible with the explanation in S&S
    that "The predicate <arg> is defined as if there were an infinite
    table of facts."  Here is an example of a predicate which would
    be *broken* by this change:

	%   sub_term(Kernel, Term)
	%   is true when Kernel is a sub-term of Term.

	sub_term(Term, Term).
	sub_term(SubTerm, Term) :-
		nonvar(Term),
		functor(Term, _, N),
		sub_term_scan(N, Term, SubTerm).

	sub_term_scan(N, Term, SubTerm) :-
		arg(N, Term, Arg),
		sub_term(SubTerm, Arg).
	sub_term_scan(N, Term, SubTerm) :-
		N > 1,
		M is N-1,
		sub_term_scan(M, Term, SubTerm).

    This code is not found in Sterling & Shapiro, but according to the
    definition of arg/3 found on p138 it is perfectly legal.  In WG17's
    N40, it _MUST_ break.  If N40's definition is adopted, you will
    not be able to use Sterling & Shapiro as a guide.

assert/1		common		DELETED (new incompatible assert/2)
asserta/1		common		DELETED (new incompatible asserta/2)
assertz/1		common		DELETED (new incompatible assertz/2)
retract/1		common		DELETED (new incompatible retract/2)
abolish/2		common		DELETED (new incompatible abolish/1)

    Note:  I personally strongly dislike abolish/2, as it is inconsistent
    with other DEC-10 Prolog operations.  The general convention is that
    a meta-predicate which is free of side effects takes a single predicate
    specification in the form of a term which looks like a call to that
    predicate, e.g. current_predicate(_, foo(X,Y,Z)) is true if foo/3 is
    a user-defined predicate, while a meta-predicate which changes the
    state of the system in any way takes an argument which specifies a set
    of predicates.  So abolish/2 is NOT consistent with this convention,
    and N40's abolish/1 -- which presents the same interface as Quintus's
    abolish/1 *IS* consistent with this convention.  This is just about
    the only case where I like N40's version better than what is common.
    Unfortunately, my likes and dislikes really don't matter; abolish/2
    _is_ the Common Prolog operation and abolish/1 _isn't_.  It is fair
    enough to add abolish/1 and recommend that abolish/2 should no longer
    be used, but it is _not_ fair enough to delete abolish/2.  Worse still,
    N40's particular version of abolish/1 cannot be used to implement
    abolish/2:
	abolish(F, N) :- abolish([F/N]).
    won't work because the former abolishes static predicates and the latter
    does not (in N40, that is; in Quintus Prolog it works just fine).

consult/1		common		CHANGED
reconsult/1		common		CHANGED
[...]			common		DELETED

    Note:  Quintus Prolog and some others have deleted consult/1 and
    renamed reconsult/1 to consult/1.  This one is debateable.
    Note:  that's not what N40 changed, though.  N40 changed the
    argument from a file name to a stream.

clause/2		common		present
listing/0		common		present
listing/1		common		present

read/1			common		present

    Note:  Sterling and Shapiro do not describe Prolog syntax in detail.
    N40 DELETES character lists, which does break S&S, but that's one of
    the few explicit differences.

sread/2			private		provided as read_with_names/2

    Note:  this operation was present in the public-domain implementation
    of DEC-10 Prolog syntax as read/2; it was also provided in some versions
    of C-Prolog as read/2, and is in the Quintus library as portable_read/2.
    A similar operation is in NU Prolog as readTerm/3.  The name and
    interface in N40 are quite sensible, and as this is one of the areas
    where there was no agreement, I think read_with_names/2 is a Good Thing.

write/1			common		present (vague)
writeq/1		common		present (vague)
display/1		common		present (vague)
displayq/1		private
print/1			common		modified (probably unintentional)

    Note:  in Common Prolog, if you call print(f(X,Y)), and your definition
    of portray/1 does not match f(X,Y), print/1 then checks to see whether
    'f' is an infix operator.  If it is, it will print(X), write f suitably,
    and print(Y), possibly with parentheses around the whole.  But N40
    states clearly in 9.12.2.1 c) that the principal function symbol must
    be printed first and then the arguments, and there is no exception for
    infix or postfix operators.  Thus if there is no portray rule which
    matches A<B, the command
	print(1 < 2)
    will write out "1 < 2" in Common Prolog, but must apparently write
    something like "<(1, 2)" in WG17 Prolog.  As I say, this is probably
    unintentional, but there is nothing whatsoever in 9.12.2 to say that
    print/1 ever has anything to do with operators.

see/1			common		DELETED
seeing/1		common		DELETED
seen/0			common		DELETED
tell/1			common		DELETED
telling/1		common		DELETED
told/0			common		DELETED

    Note:  it _is_ possible to define these operations in WG17 Prolog,
    but it is impossible to use close/1 with these files.  N41 suggests
    how see/1 might be coded, but the code is seriously incorrect,
    which suggests that see/1 ought to be specified in the standard so
    that other potential implementors will get it right...

flush/0			private

    Note:  some such operation is important, but it has a variety of
    names.  In DEC-10 Prolog it was ttyflush/0 only.  In Quintus Prolog
    it is ttyflush/0 and flush_output/1.  Unfortunately, it is rather
    OS-dependent.  (UNIX programmers need to beware of the distinction
    between fflush() and fsync().)

get/1			common		DELETED
get0/1			common		DELETED
skip/1			common		DELETED
put/1			common		DELETED
tab/1			common		DELETED
nl/0			common		DELETED
tty*/1			common		DELETED

    Note:  I've summarised ttyget, ttyget0, ttyput, ttytab, ttyskip, ttynl
    in one line because I don't think they are very important, but that's
    just my own taste, and it would certainly be easy enough to specify
    them in the standard.  I regard the dropping of nl/0 as excessively
    odd; it is important for portability reasons to keep the value of the
    new-line character (or whether it is one character or two or what)
    out of code.

op/3			common		present (modified)

    Note:  in Common Prolog the third argument of op/3 can be a list of
    atoms, in N40 (and clarified in N41) this must be reported as an
    error.  Also in N40 you are not allowed to have an operator which is
    both infix and postfix.

save/1			common		DELETED

    Note:  this is admittedly OS-dependent, and with shared libraries,
    memory areas mapped to files, and so on, it is increasibly hard to
    implement, let alone define.  Something could perhaps be done along
    the lines of Quintus' save_program/1, but on the whole it is reasonable
    to leave this out of the present standard.

log/0			private

    Note:  actually, it does exist in DEC-10 Prolog, but the operation has
    been dropped from some other Prologs.  Debateable.

true/0			common		present
fail/0			common		present
!			common		present
exit/0			private

    Note:  the Common Prolog operation is not exit/0 but halt/0, and that
    _is_ included in N40.  So is a new halt/1 operation.

abort/0			common		DELETED
call/1			common		present
not/1			commonish	RENAMED

    Note:  the only negation operation in DEC-10 Prolog is the
    "unprovable" predicate (\+)/1 (think of a crossed-out |-). 
    not/1 is a DEC-10 library predicate which reports an error
    if its argument is not sufficiently instantiated to be sound.
    Many Common Prologs identify not/1 and (\+)/1, which is a
    pity.  WG17 Prolog does not use either name, but introduces
    a new name:  fail_if.

name/2			common		DELETED

    Note:  name/2 can be used to convert between numbers and character
    lists, an operation which Quintus Prolog calls number_chars/2.  It
    has to be admitted that name/2 was rather muddled in DEC-10 Prolog,
    and that it _ought_ to be supplemented by new atom_chars/2 and
    number_chars/2 predicates, or something like that, but it should
    not be deleted, and the new scheme should not provide _less_ power!

    To convert between numbers and character lists in WG17 Prolog, the
    following definitions appear to be necessary:

	number_chars(Number, Chars) :-
	    (	number(Number),
		!,
		swritef(String, q, Number),
		string_chars(String, Chars)
	    ;	var(Number),
		!,
		string_chars(String, Chars),
		strlength(String, W),
		(   substring(String, _, _, "."), !,
		    sreadf(String, f(W), Number, "")
		;   substring(String, _, _, "E"), !,
		    sreadf(String, f(W), Number, "")
		;   substring(String, _, _, "e"), !,
		    sreadf(String, f(W), Number, "")
		;   sreadf(String, i(W), Number, "")
		)
	    ;   Number is Number+0
	    ).

	string_chars(String, Chars) :-
	    (	string(String),
		!,
		string_list(String, UnitStrings),
		units_chars(UnitStrings, Chars)
	    ;   var(String),
		!,
		units_chars(UnitStrings, Chars),
		string_list(String, UnitStrings)
	    ;	concat(String, String, _)
	    ).

	units_chars([], []).
	units_chars([UnitString|UnitStrings], [Char|Chars]) :-
		char_int(UnitString, Char),
		units_chars(UnitStrings, Chars).

    (No, I am _not_ sure that this is correct.  But it is the best I can
    come up with.)

repeat/0		common		present
, /2			common		present
; /2			common		present
=.. /2			common		present
= /2			common		present
\= /2			commonish	present

    Note:  (\=)/2 is not built into DEC-10 Prolog or Quintus Prolog, but
    is a library predicate in both.  It is built into many other Common
    Prologs.

== /2			common		present
\== /2			common		present
system/1		private

    Note:  some such operation is provided in most Prologs these days.
    In Quintus Prolog it is unix(system(X)) or vms(dcl(X)) or
    cms(system(X)) or whatever, and there is a library predicate
    system/1.  In NU Prolog it is system/1.  In LPA Prolog on the PC
    it is dos/1.  system/1 is a good name for it, and it might as well
    be in the standard.

systemp/2		private

    Note:  in NU Prolog this is systemPredicate/1 and systemPredicate/2.
    In Quintus Prolog it is predicate_property(Goal, built_in).  In LPA
    MacProlog, it is sdef/1.  It's clear that you want access to this
    information, but there has been no common way of doing it in the past,
    and it would be better to have a single predicate like the Quintus
    one than half a dozen separate ones.

save_term/1		private
unsave_term/1		private

    Note:  these commands are not listed in the index, and I don't think
    the text uses them.  The text does describe set_of/3 and bag_of/3
    (which are subtly different from setof/3 and bagof/3; the change is
    not an improvement but introduces a bug).  Program 17.3 is a version
    of findall/3, but it is rather badly broken.  For example, if you
    call find_all_dl(., fail, X) it should return a representation of
    the empty list, but instead it fails, leaving $instance($mark) in
    the data base.

    The fact that both Clocksin&Mellish and Sterling&Shapiro managed to
    produce buggy versions of findall/3 suggests that findall/3 should
    be in the standard and should be spelled out with the utmost clarity.
    It _is_ in the standard, except that WG17 have changed the name from
    findall/3 to bag/3.  (There is no set/3, in case you were wondering.)
    As to whether bag/3 is described "with the utmost clarity", I do not
    find it so, but you ought to get a copy of the draft and judge for
    yourselves.  (It _is_ described formally, as indeed it should be,
    it's just that I don't understand the formal description.)

member/2		commonish
append/3		commonish

    Note:  these two operations can easily be defined in Prolog, and in
    many Common Prologs they are library predicates, not built in.  The
    usual code for them will work fine in WG17 Prolog.

iterate/1		private

    This can be coded in Common Prolog as

	iterate(Goal) :- call( (repeat, \+ Goal) -> true ).

    It can be coded in WG17 Prolog as

	iterate(Goal) :- call( (repeat, fail_if(Goal), !) ).

    or as

	iterate(Goal) :- once( (repeat, fail_if(Goal)) ).

    I can't think of a good use for it, but it's definable, so no harm done.

fork_exec/2		private

    Note:  this is not listed in the index of S&S and the text does not
    appear to describe it.  It sounds OS-dependent, whatever it is.

ancestor/2		private
cutg/1			private
retry/1			private

    Note:  these operations are apparently used in the WISDOM Prolog
    debugger.  There is a Common Prolog predicate ancestors/1 in terms
    of which ancestor/2 is definable.  cutg/1 is a form of ancestral cut.
    Debugging is outside the scope of the standard, and other Prologs
    use different support predicates.

< /2			common		modified
:= /2			private
is /2			common		modified

    Note:  := /2 is a private alias for is/2.  I dislike it on the grounds
    that it doesn't behave like assignment, so why make it look like
    assignment?  WG17 Prolog permits the right hand side of is/2 to be a
    string, so you can say X is $foo$.  Earlier drafts had several string
    functions which have been replaced by cleaner and better predicates
    (still not as good as the ones in Xerox Quintus Prolog...), so this
    may just be a relic of the past.  Arithmetic comparisons may have
    strings in them, but must then always fail, again this appears to be
    a relic of the past.  Apart from strings, arithmetic expressions in
    WG17 Prolog are mostly an extension of expressions in Sterling & Shapiro.

				--------
				 ------
				  ----
				   --

Summary.

    If Sterling and Shapiro want to make their book compatible with WG17
    Prolog as it currently stands, they will have to make changes to every
    chapter.  My estimate is that roughly a quarter of the text will need
    to be rewritten, though all of it will have to be checked carefully.
    The amount of labour involved is roughly comparable to the amount of    
    labour required to convert an elementary Pascal textbook to an
    elementary Modula-2 textbook.