[comp.lang.prolog] BSI Proposal

cdsm@doc.ic.ac.uk (Chris Moss) (03/09/88)

In reply to: ok@quintus.UUCP (Richard A. O'Keefe)
rok>This still isn't the detailed comments, but my claim in article <736@cresswell>
that
cdsm>	(3) The attempt to describe Prolog control structures as *syntax*
cdsm>	    is fundamentally misdirected.
rok>warrants an example.  I am referring to document BSI/IST/5/15
rok> ISO/IEC JTC1 SC22 WG17 "Draft for comment: Feb 1988".
rok> 
rok> Here is the example.  In Prolog as we know and love it:
rok> 	p :- q.
rok> and
rok> 	(p :- q).
rok> are both clauses, and they are identical as clauses.  
rok> Well, in BSI Prolog, they are both
rok> clauses, but they are *different* clauses.

WRONG. The second is not allowed in the BSI form. You missed the 'h'
constraint. -- Before you point it out, there are a couple of errors in
these constraints. The version-to-be-published (the one you had is
basically for the committee) will correct it!

rok>   That is to say,
rok> 	(p :- q).
rok> is identical to the clause
rok> 	(p :- q) :- true.
rok> 
rok> Well, that's a bit surprising.  What about
rok> 	:-(p, q).
rok> which in Edinburgh Prolog is identical to the other two examples.

Oh dear. The first three times I read that, I saw:
	:- (p, q).
and thought you were talking about bracketted 'and' clauses.
And that is precisely the point. 
In English, and in most programming languages post-Fortran, spaces are
used to separate symbols which would otherwise run together. In this case
they are used for an entirely different purpose: to distinguish two
different uses of the symbol "(". Now it is a fact that most of the
typists I've ever asked to type up Prolog programs put spaces between a
predicate and its arguments
e.g.	funny ( idea ).
as do many logicians and programmers. 
(flame on)
      WHY THE HELL SHOULDN'T THEY??
(flame off!)

The reason is of course that the authors of Edinburgh Prolog thought up a
very clever way to distinguish normal form functions from prefix operators.
This means that one doesn't have to use quotes to distinguish operators in
most contexts, but can get into the weirdest messes otherwise.
In previous versions of the syntax there were two proposals: the other was
to use quotes to disable operators as is done by several systems (can I
mention BIM-Prolog too?). This got so much flack that we've attempted to
move nearer the Edinburgh approach, to the extent that spaces ARE still
important in one context: in "- (A)", the minus is a prefix operator and
in "-(A)" it is a function symbol (they mean the same anyway). But
everywhere else they are optional. I think that's an improvement.

rok> Let's look at rule 5.4.
rok> 
rok> 5.4	   term          = atom, (next bracket | sep bracket), termlist, ")" ;
rok>   The first time I read this rule, I interpreted
rok> it as meaning that a function symbol could not be a prefix operator,
rok> which would make :-(p,q) illegal.

You still haven't got the idea. :-(p,q) is illegal because there's no way
to get it into the grammar. You could say ':-'(p,q) 

rok> The new rule seems very confusing to me.  Pointless too.

You could get used to it if you tried hard :-)

rok> So, three formerly identical versions of a clause
rok> 	p :- q.
rok> 	(p :- q).
rok> 	:-(p, q).
rok> all mean something different in BSI Prolog.

No, the latter two are illegal!

rok> The grimoire makes it plain that
rok> 	A , B
rok> and	A & B		<--- BIG MISTAKE
rok> are both mapped to sys(and,[A,B]), but whether either of these is the
rok> same as ','(A,B) or '&'(A,B) is not said.  

The only context in which they are the same is when they are passed to
'call' or another meta-primitive which maps terms to predicates.


rok> If we take the "Abstract"
rok> lines seriously, it would appear that ','(A,B) and '&'(A,B) are
rok> distinct terms, neither of which is the same as (A,B) or (A&B).


rok> Oddly enough, if one takes the grimoire literally, the user CAN
rok> declare ',' and '&' as operators, and can use them in that form.

The syntax (not surprisingly) does not specify the semantics of the 'op'
predicate. So don't assume you can by looking there...

rok> and	A & B	<--- BIG MISTAKE
...
rok> and	A | B	<--- DEC-10 Prolog mistake retained in BSI Prolog

A DEC-10 mistake perpetuated, of course, by Quintus, Richard's company. He
obviously hasn't found it an issue worth resigning over :-)

Seriously, I'd be glad of feedback on this issue. 
Do people want: (1) just , and ; (2) allow the rather anachronistic | as well
as ; or (3) the full freedom to use logical symbols or natural language
symbols as they think fit?

rok> {Note that ;(a,b), legal in Edinburgh Prolog, is NOT legal in BSI Prolog.}
...
rok> Oddly enough, if one takes the grimoire literally, the user CAN
rok> declare ';' and '|' as operators, and can use them in that form.

In the standard everything that applies to ',' applies to ';' (unlike
Edinburgh which has different rules fo each)

rok> It seems quite clear from this that
rok> [a]	( p -> q ; r )
rok> means
rok> 	sys(ifthenelse,[func(p,[]),func(q,[]),func(r,[])])
rok> but that
rok> [b]	( p '->' q ; r )
rok> [c]	( ->(p, q) ; r )
rok> if legal, must mean
rok> 	sys(or,[func(->,[func(p,[]),func(q,[])]),func(r,[])])

To reiterate, [b] and [c] (as with the other operators) are illegal, but 
	('->'(p, q) ; r)
would have the interpretation you want.

rok> A similar intention may exist in rules 2.2 (:-), 2.3 (?-), 2.4 (:-),
rok> and 2.5 (-->) where the quoted items are also legal atoms.  But
rok> that's *not* what the grimoire actually says!

The S-expression syntax has exceptions in all these cases, it should have
been in the E-syntax too (in L7). None of these symbols should be atoms.

rok> There's something strange about the treatment of "{" and "}" in BSI
rok> Prolog.  According to the grimoire (rule 5.6),
rok> 	{ X }	means	pred('{}',[X])

a typo -- it should have been func -- already corrected.


rok> I'm quite sure that the fact that rules L7, L29, L30, and L15
rok> imply that <)> is a valid token is a mistake, but I just thought
rok> I'd mention it.  

in rule L15, ")" was mistyped as "(". Corrected (in the obvious way).

rok> Another probable glitch is the fact that the
rok> only way to get a backslash character in a quoted atom is to
rok> write its octal code.  (According to rule L12, \\ is NOT a legal
rok> escape sequence.)  

That's been there for a year!! How come no-one pointed it out??
Thanks, accepted.

rok> A complaint here:  if character escaping is
rok> supposed to be C-like, is it too much to ask that it should *BE*
rok> C-like?  The ANSI C escape sequences
rok> 	\a	(audible alarm)
rok> 	\v	(vertical tab)
rok> 	\\
rok> 	\?
rok> are completely missing.

I don't have a copy of ANSI C. Will be considered.

rok> The following clauses, valid in Edinburgh Prolog, are illegal in BSI Prolog.
rok> 
rok> 	/** By L22, this is not a legal comment **/

Thankyou Richard. L22 should of course read something like:

comment chars = character - "*", comment chars	| "*", end comment;
end comment = "/" | "*", end comment | character - ("*"|"/"), comment chars;

For those who are unfamiliar with this version of BNF, it has itself been
defined by a British Standard! (BS6154). "-" is for exceptions, of course.

rok>	compare(R, X, Y) :-
rok>		( X @> Y -> R = >
rok>		; X @< Y -> R = <
rok>		;	    R = =
rok>		).

Yes, thank goodness this is illegal. If you want to write it, try:

		( X @> Y -> R = (>)
etc.

rok>	not Goal :-		% "not" is not a built-in operator
rok>	    (	ground(Goal) -> \+ Goal		% neither is "\+".
rok>	    ;	signal_error(instantiation_fault(Goal,0))
rok>	    ).

This is NOT illegal if you define 'not' as an operator.

rok>[The fact that the grammar proper has no negation proper is no accident.
rok> The grammar in the grimoire defines only operators with at the level of
rok> comma and weaker.  Negation binds more tightly than comma, so it would
rok> have to be in the table of built-in operators.  The absence of any
rok> negation operator from that table may be a mistake, or it may not.  It
rok> may be the intention that one has to write \+(Goal).
rok>]

If you remember, Richard, "not" WAS defined as an operator in a previous
version of the syntax. However various members of the logic programming
community (including you if I am not mistaken) have objected strenuously
to the use of such a logical name for something which (implemented in
the usual dirty fashion by means of cut) clearly is NOT logical. Thus the
current BIP proposal contains only a predicate called "fail_if" which is
at least honest if not elegant.

rok>If we take the lexical rules (specifically L0,L1,L2) and rule 0 of
rok>the grimoire literally, any program containing a comment is illegal.
rok>The lexical rules very clearly classify comments as tokens, and as
rok>clearly return ALL the tokens, and rule 0 takes ALL the tokens and
rok>feeds them to the grimoire rules.  There is nothing in the grimoire
rok>which says that comments are dropped!

Not true; the version you have does not explicitly make any correspondence
between tokens and programs (there's no abstract part in the lexical
section). It was agreed last Wednesday that it should and this is in the
course of being added to make this very point explicit.

rok>The BSI committee started work in 1984.  I know that it takes a day to
rok>get a DEC-10 Prolog lexer written and tested.  Does it really take a
rok>comittee over three years to get this far?  Would it have taken that
rok>long if they hadn't decided to design their own language?  At the Boston
rok>Logic Programming conference, Frank McCabe assured us that the standard
rok>would be ready the following year.  What a good thing it wasn't, eh?

I have no intention of creating a new language. If you've ever worked on a
standards committee you would know it is impossible to get it done in a
year (let's watch the LISP folks prove me wrong :-). 
It's now got as far as being accepted by the proper number of ISO
countries with the first ISO meeting at the end of the month.
Lots of people have wanted their own pet ideas in the standard and
doubtless it won't please everybody. But it would be nice to get it
finished.

Thanks for your comments, Richard. I look forward to your replies.
Chris Moss.

ok@quintus.UUCP (Richard A. O'Keefe) (03/14/88)

In article <229@gould.doc.ic.ac.uk>, cdsm@doc.ic.ac.uk (Chris Moss) writes:
> rok> Here is the example.  In Prolog as we know and love it:
> rok> 	p :- q.
> rok> and
> rok> 	(p :- q).
> rok> are both clauses, and they are identical as clauses.  
> rok> Well, in BSI Prolog, they are both
> rok> clauses, but they are *different* clauses.
> 
> WRONG. The second is not allowed in the BSI form. You missed the 'h'

Well, yes and no.  The grimoire doesn't explain what the Constraint
line means, and I had to guess.  The "February 88" draft has three
rules (5.4, 5.4 (sic), and 5.5) for parentheses, and the "Feb 88" one
has only one (5.5).  If I had taken rule 5.5 in the "Feb 88" draft
seriously, I would have been forced to the conclusion that (0) was not
a legal term in BSI Prolog!  I jumped to the conclusion that rule 5.5
should have had 'h' as its left-hand constraint because fairly serious
nonsense would result if 5.5 wasn't fixed somehow.

> And that is precisely the point. 
> In English, and in most programming languages post-Fortran, spaces are
> used to separate symbols which would otherwise run together. In this case
> they are used for an entirely different purpose: to distinguish two
> different uses of the symbol "(". Now it is a fact that most of the

Well, it depends what you mean by a symbol.  I regard "fred(" or ":-("
as a single token.  It seems just as reasonable to do that as to regard
"1.0e-4" as a single token, or do you want to allow spaces there too?

> typists I've ever asked to type up Prolog programs put spaces between a
> predicate and its arguments
> e.g.	funny ( idea ).
> as do many logicians and programmers. 
> (flame on)
>       WHY THE HELL SHOULDN'T THEY??
> (flame off!)

I know, I've had that kind of trouble with typists too.  I had a perfectly
straightforward piece of ordinary mathematical text which I had to send
back three times once, and finally had to type it myself.

Putting a space after a left parenthesis or before a right parenthesis
is appallingly bad English punctuation, so it sounds as though you must
have a lot of trouble with your typists working on English too.

None of the mathematical or logical texts on my bookshelves puts a space
between a function symbol or predicate symbol and its left parenthesis,
EXCEPT when the function or predicate symbol is UNARY.  When you are
using "Curried" functions, they are of course unary, so if you have
defined
	f = lambda x. lambda y. lambda z. h(x,g(y),z)
it is entirely appropriate to write
	f 1
and 	f 2 3
but if you have defined
	f = lambda(x,y,z). h(x,g(y),z)
it is good style to write
	f(1,2,3)
rather than
	f (1,2,3)

Many logicians and mathematicians habitually use Greek letters,
subscripts and superscripts, and do exotic things like using (( as
an infix relational operator.

>       WHY THE HELL SHOULDN'T THEY??

You tell me.

Do you regard the fact that a typist is likely to mistake an iota for
an i or an epsilon for an e as an argument that mathematiciains should
not use Greek letters?  Should we outlaw vertical bars because bad
typists think they are solidii or ells or capital Is?  And while we're
at it, a lot of people like using hyphens and don't understand or
don't like the break character, so shouldn't we throw out "_" and
allow instead identifiers like this-is-one-token.  After all, typists
often mistake "_" for "-".

As Chris Moss says, most languages since Fortran regard blanks as
significant.  Surely it is inconsistent to argue that
	"RED O" and "REDO"
are different, and that is a Good Thing, but
	"red (O)" and "red(O)"
being different is a Bad Thing?  Blanks are being treated as
significant in both cases.  "RED O" and "red (" are both two tokens,
and "REDO" and "red(" are both one token; it's exactly the same thing.
What's sauce for the goose is sauce for the gander.

As it happens, I'm an Algol 68 fan.  I like having spaces inside
identifiers, rather than underscores or hyphens.  I even have a version
of the public-domain parser which lets me treat

	list length([], 0).
	list length([_|Tail], succ(N)) :-
		list length(Tail, N).

as Prolog.  ("list length" turns into "list_length".)  Does this mean I
think the standard should allow spaces inside identifiers?  No way!
I think this is 10% better than what we have now, which is good enough
to put it in some other language, but it's nowhere _near_ enough of an
improvement to change the language we already have.

> You still haven't got the idea. :-(p,q) is illegal because there's no way
> to get it into the grammar. You could say ':-'(p,q) 

By lexical rule L29, ":" and "-" are graphic characters.
By lexical rule L7, ":-" is a graphic symbol.
By lexical rule L3, ":-" is thus an atom.

By syntax rule 5.4, <atom> "(" <termlist> ")" is a term/h.
The only constraint is that if <atom> is a prefix operator, there must
be no space between <atom> and "(".  Therefore :-(p,q) ***IS*** in the
grammar.

> rok> The grimoire makes it plain that
> rok> 	A , B
> rok> and	A & B		<--- BIG MISTAKE
> rok> are both mapped to sys(and,[A,B]), but whether either of these is the
> rok> same as ','(A,B) or '&'(A,B) is not said.  
> 
> The only context in which they are the same is when they are passed to
> 'call' or another meta-primitive which maps terms to predicates.

No, the grimoire says very very clearly that both (a,b) and (a&b)
are mapped to the same Abstract, namely

	sys(and, [func(a,[]), func(b,[])])

***LEXICAL*** rule L19 says
	and symbol = "&" | "," ;
so when we get to syntax rule

4.1		goals		= term, [and symbol, goals] ;
Constraint	X		  X		     X
Abstract	sys(and,[A,B])    A		     B

there is no possibility of distinguishing between "," and "&": there is
*NOTHING* associated with the "and symbol" which can participate in the
Abstract.

"&" is not equivalent to "," between <function(> and <)> or between
<[> and <]>.  But functioning as an "and symbol" it is quite
indistiguishable from ",", at least according to the grimoire, and
that is all I can go on.

> rok> Oddly enough, if one takes the grimoire literally, the user CAN
> rok> declare ',' and '&' as operators, and can use them in that form.
> 
> The syntax (not surprisingly) does not specify the semantics of the 'op'
> predicate. So don't assume you can by looking there...

Quite right.  In fact, since the grimoire says on page 5 "The following
table defines the "is_op" table used in clauses 8-10 above", it would be
closer to the truth to say that the grimoire forbids user-defined
operators entirely.  Silly me.

But the question of which symbols the programmer can declare as operators
is surely a syntactic question.  If I want to know what operators I can
declare in Algol 68, I look in the grammar.  If I want to know what
operators I can overload in ADA, I look in the grammar.  If I want to know
what operators I can declare in Pop-2, I look in the grammar, which tells me
that operators look just like other symbols.  If not in the grimoire,
where SHOULD I look to find out what operators I can declare?

> rok> and	A | B	<--- DEC-10 Prolog mistake retained in BSI Prolog
> 
> A DEC-10 mistake perpetuated, of course, by Quintus, Richard's company. He
> obviously hasn't found it an issue worth resigning over :-)

I agree that it is a mistake, from the point of view of language design.
I keep asking people here at Quintus not to use it, and when I edit
any system files I surreptitiously change "|"s to ";"s.  But Quintus
don't claim to have a SUPERIOR syntax, they claim to have a COMPATIBLE
syntax, and compatible means compatible, even with features I might not
happen to like.  I think this line has been misread:  I meant the
comment to indicate that (a) I don't like it, but (b) because it is part
of the de facto standard it *should* be retained in BSI Prolog.

> Do people want: (3) the full freedom to use logical symbols or
> natural language symbols as they think fit?

Everyone will go for (3), of course.  But that is something of a red
herring, as BSI Prolog won't allow it.  Sure I'd like to be able to
write
	every group is a monoid.
Oh, "natural language symbols" didn't mean that?  Silly me.
I'd like a language in which I could use branching quantifiers and
modal operators.  Oh, "logical symbols" didn't mean that?  Silly me.

> rok> It seems quite clear from this that
> rok> [a]	( p -> q ; r )
> rok> means
> rok> 	sys(ifthenelse,[func(p,[]),func(q,[]),func(r,[])])
> rok> but that
> rok> [b]	( p '->' q ; r )
> rok> [c]	( ->(p, q) ; r )
> rok> if legal, must mean
> rok> 	sys(or,[func(->,[func(p,[]),func(q,[])]),func(r,[])])
> 
> To reiterate, [b] and [c] (as with the other operators) are illegal, but 
> 	('->'(p, q) ; r)
> would have the interpretation you want.

The interpretation I *want* is the one [a] gets.
What I *fear* is that ('->'(p,q) ; r) will get the *other* one.

[b] would be illegal for the simple reason that the grimoire
does not list "->" and ";" at the foot of page 5 (the table of built in
operators) and provides no other means of making ANY atoms legal operators.
However,

By lexical rule L29, "-" and ">" are graphic characters.
By lexical rule L6, "->" is a graphic symbol.
By lexical rule L3, "->" is an atom.

By lexical rules L4 and L3, "p" and "q" are atoms.

By syntax rule 5.3, p and q are terms, and by syntax rule 6, "p, q"
is a termlist.  By syntax rule 5.4, "->(p, q)" is therefore a legal term.
Indeed, since "->" is not a prefix operator, "->  (p, q)" is also a legal
term.

So [c] is ***NOT*** illegal.  Even if operators had to be quoted,
by virtue of the fact that the control structures are hardwired into
the grammar, '->' and ';' do not appear in is_op/3, the table of built-in
operators, it follows from syntax rules 8, 9, and 10 that -> is neither
a prefix op, nor a postfix op, nor an infix op.  Even if it were an
infix op, that would not make ->(p,q) illegal, at least not in the
version of the grimoire that I was citing (the "Feb 88" one, not the
"February 88" one).

> 
> rok> A similar intention may exist in rules 2.2 (:-), 2.3 (?-), 2.4 (:-),
> rok> and 2.5 (-->) where the quoted items are also legal atoms.  But
> rok> that's *not* what the grimoire actually says!
> 
> The S-expression syntax has exceptions in all these cases, it should have
> been in the E-syntax too (in L7). None of these symbols should be atoms.

So when Chris Moss said above:
> You still haven't got the idea. :-(p,q) is illegal because there's no way
> to get it into the grammar. You could say ':-'(p,q) 
what he REALLY meant was "there is a mistake in the version of the
grimoire you have, you have correctly understood what it said, but
that's not what we meant."

> rok> I'm quite sure that the fact that rules L7, L29, L30, and L15
> rok> imply that <)> is a valid token is a mistake, but I just thought
> rok> I'd mention it.  
> 
> in rule L15, ")" was mistyped as "(". Corrected (in the obvious way).
> 
Simply changing "(" to ")" would have the result of making <(> legal.
Presumably _both_ "(" and ")" are "solo symbol"s.

> rok>	compare(R, X, Y) :-
> rok>		( X @> Y -> R = >
> rok>		; X @< Y -> R = <
> rok>		;	    R = =
> rok>		).
> 
> Yes, thank goodness this is illegal. If you want to write it, try:
> 
I see, you think it is nasty of me to stop people writing
	ugly
								(
	code							)
by saying that the standard should stick with what we've already got,
but it's fine for you to take away something I'm already using.  TANJ!

> This is NOT illegal if you define 'not' as an operator.

My point was not that "not" is not an operator, but that NEITHER
"not" NOR the preferred "\+" is an operator.

> rok>If we take the lexical rules (specifically L0,L1,L2) and rule 0 of
> rok>the grimoire literally, any program containing a comment is illegal.
> rok>The lexical rules very clearly classify comments as tokens, and as
> rok>clearly return ALL the tokens, and rule 0 takes ALL the tokens and
> rok>feeds them to the grimoire rules.  There is nothing in the grimoire
> rok>which says that comments are dropped!
> 
> Not true; the version you have does not explicitly make any correspondence
> between tokens and programs (there's no abstract part in the lexical
> section). It was agreed last Wednesday that it should and this is in the
> course of being added to make this very point explicit.
> 
Not true.  I referred (as quoted!) to syntax rule 0, which is explicitly
described as "the interface between the two sections".  If this does not
"explicitly make any correspondence between tokens and programs", what
DOES it do?

> I have no intention of creating a new language.

About your intentions, I have nothing to say.  You are the only authority.
About your *actions*, I can only say that whatever you intend, BSI Prolog
is about as different from Edinburgh Prolog as Turbo Pascal is from ISO
Pascal.

> It's now got as far as being accepted by the proper number of ISO
> countries with the first ISO meeting at the end of the month.

When I saw that the BSI committee had had the effrontery to propose their
stuff to ISO, I was speechless with rage.  I think the ISO approach to
internetworking is enough to show that being accepted by some number of
ISO countries is no guarantee of quality.

> For those who are unfamiliar with this version of BNF, it has itself been
> defined by a British Standard! (BS6154). "-" is for exceptions, of course.

This applies to the rules proper only.  It does not apply to the lines
labelled "Constraint", "Abstract", "Priority", "Input", "Output".
There are at least two problems with these additional lines.

The first, of course, is that they use a two-dimensional format where
the number of spaces is vitally significant:

	foo	= baz, ugh ;
Thingy	X	  X	

and
	foo	= baz, ugh ;
Thingy	X	       X

are *very* different.  If allowing arbitrary amounts of space inside
a <function(> token is such a wonderful thing, the grimoire should take
its own medicine.  Perhaps something like
	foo	= baz, ugh ;
Thingy	X	: X,   _   ;

and
	foo	= baz, ugh ;
Thingy	X	: _,   X   ;

One also has to watch out for the fact that some lines are omitted from
some rules.  I believe it to be the case that to determine which attributes
are relevant to what non-terminals it is necessary to examine the entire
grammar.  

But the second, and biggest problem, is that not only are these new lines
not part of BS6154, the whole thing is a new formalism which is not
described in any of the documents that the BSI committee have sent me.
What does it mean when a rule of the grimoire says

Rule	 foo = 	baz,  [ ugh ] ;
Abstract f(X,Y)	X	Y

I *think* it means

	 foo =	baz, ugh ;
	 f(X,Y)  X    Y
+
	 foo =   baz ;
	 f(X,[])

but I can find nothing that says so.  What does it mean when a rule of
the grimoire uses

Rule	 		.... { stuff } ....
Abstract			X
Other				k

I *think* it means

Rule			.... stuff-star ....
Abstract			X
Other				k
where

Rule	 stuff-star = empty ;
Abstract []
Other	 K	
+
Rule	 stuff-star = stuff, stuff-star ;
Abstract [X|Xs]		X	Xs
Other	 K		K	K

but I can find nothing that says so, neither is it said anywhere which
attributes participate in listification and which do not.  Now the one
thing a standard _must_ not do is leave you guessing!

> Lots of people have wanted their own pet ideas in the standard ...

I don't want *ANY* of *my* pet ideas in the standard.
Look, if you took Fernando's version of C Prolog (not mine)
and stamped "BSI" on it, I wouldn't mind much.
Dash it, you could take *ALS* Prolog and stamp "BSI" on it, and
I'd think more highly of the BSI committee.
All I want is a standard which is close to existing practice and
spells things out in rather more detail than most manuals.

I want everyone reading this to understand my position clearly:
    (1) what would be a good syntax for a logic programming language?
    (2) what should the standard syntax be?
I regard these as two very different questions.  I think Pascal syntax
is little short of insane, but that doesn't mean that I think the Pascal
_standard_ should have departed from it.  I think C syntax is bizarre,
but that doesn't mean that I think X3J11 should redesign it.  When I
write down logical clauses, I use '<-" for if, '&' for and, '|' for
or, and am as likely to use ';' at the end as '.'.  So what?  That's
not the way Edinburgh Prolog ***IS***.

A committee such as the BSI Prolog one is not the best way to answer
question (1).  The right thing to do is to perform experiments.


Richard (there is little so bad that changing it won't make it worse) O'Keefe

micha@ecrcvax.UUCP (Micha Meier) (03/17/88)

In article <771@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>As Chris Moss says, most languages since Fortran regard blanks as
>significant.  Surely it is inconsistent to argue that
>	"RED O" and "REDO"
>are different, and that is a Good Thing, but
>	"red (O)" and "red(O)"
>being different is a Bad Thing?  Blanks are being treated as
>significant in both cases.  "RED O" and "red (" are both two tokens,
>and "REDO" and "red(" are both one token; it's exactly the same thing.
>What's sauce for the goose is sauce for the gander.

	I'm no fan of the allowed space between the functor and
	the opening parenthesis, but this does not seem to me as
	a good argument. In the usual languages blankspaces are
	allowed between characters of different classes (in the POP
	meaning of character classes), with some exceptions like
	e.g. the floating point constants. From this point of view
	a space between "red" and "(" seems rather natural,
	to say that "red(" is one token seems to me at least arguable
	(easy to implement, I admit).

	But there are other consequences of this BSI rule - is there any
	reasonable argument to forbid binary operators that start with
	a capital letter or that contain letters and graphic chars?

	Actually, we have implemented the BSI standard in our Sepia,
	(it's probably one of the first implementations)
	but I have to admit that one of the first things to provide
	was a switch to be able to switch it off. There is a long list
	of problems we have encountered, we are going to pass them to
	BSI soon. I have appreciated to have a minimal list of
	built-ins provided by BSI, but the description contains so
	many errors that one has really to take care when implementing
	them. My global impression from BSI is, I'm afraid, close
	to that of R.A.O'K, it is a new language, and very
	difficult to implement. I've never really understood the grammar
	and the 'Formal Specification of Prolog', though :-)

--Micha

ok@quintus.UUCP (Richard A. O'Keefe) (03/18/88)

In article <517@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
> In article <771@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
> >As Chris Moss says, most languages since Fortran regard blanks as
> >significant.  Surely it is inconsistent to argue that
> >	"RED O" and "REDO"
> >are different, and that is a Good Thing, but
> >	"red (O)" and "red(O)"
> >being different is a Bad Thing?

> 	I'm no fan of the allowed space between the functor and
> 	the opening parenthesis, but this does not seem to me as
> 	a good argument. In the usual languages blankspaces are
> 	allowed between characters of different classes (in the POP
> 	meaning of character classes), with some exceptions like
> 	e.g. the floating point constants. From this point of view
> 	a space between "red" and "(" seems rather natural,
> 	to say that "red(" is one token seems to me at least arguable
> 	(easy to implement, I admit).
> 
Well, I have to admit that considered as an argument for distinguishing
between "red (O)" and "red(O)", it's rather feeble.  Plainly I need to
take a course in effective communication, because the point I intended
to make is that the BSI Junta are in no position to cast the first stone.
I have a better example to support that position, which is that in one
draft of the BSI grammar
	-1	is a negative number, but
	- 1	means -(1).
I do not believe that this is intended to be a permanent feature of BSI
Prolog.  Which brings me to the next point:

> 	Actually, we have implemented the BSI standard in our Sepia,
> 	(it's probably one of the first implementations)

Which version of BSI Prolog have you implemented?  It hasn't really been
fair of me to criticise the grimoire, because the "Feb 88" draft is
dramatically different from the "February 88" draft.  Early versions of
BSI Prolog were essentially Sigma Prolog.  Mid-range versions of the BSI
Prolog builtins are pretty much ESI Prolog 2, including file position
operations (seek/2, at/2) which don't make much sense except under MS-DOS
or UNIX, and weren't all that brilliant if you wanted to support Kanji
under UNIX.  The latest stuff is a bit closer to Edinburgh Prolog.

There was a real gem in 1987 where they decided that because they now
had strings, they didn't need nl/0.  (No smiley, this is true!)
PS 176 lists nonvar/1 and nl/0 in section 1.15 "Predicates rejected
for the standard."  That was February 1987, mind you, which was only
(:-) a little over two years since they started.
[Pause for 10 minutes to locate more recent documentation.]
According to PS/230 (dated November 1987):
[1]	at/2 and seek/2 are still there
	There is a clause/1 but no clause/2
[2]	length/2 is "rejected"
[3]	nl/0 is "rejected"
	nonvar/1 is "rejected"
[4]	see/1, seeing/1, seen/0, tell/1, telling/1, told/0 are "rejected"
	setof/3 and bagof/3 are replaced by set/3 and bag/3
[5]	sort/2 is present, but keysort/2 is missing without comment.

[1] at(+Stream, -Position) tells you where you are.
    The text says that Position might be some sort of record.
    seek(+Stream, +Position) goes to a particular place.
    The text explicitly says that Position=300 must be accepted.
    It is required that at(S, 0) when S is at its beginning, and
    that seek(S, 0) will rewind S.  (Why not, like C, admit that
    stream positions are system-dependent, and have a rewind/1?
    Idunno.)  It is further required that there is a constant E
    such that end_of_file_mark(E) and at(S, E) iff S is at its
    end and that seek(S, E) will position the stream at the end.
    Logically, this entails that E==0 and that all streams must
    be empty.  (The proof is obvious.)

[2] length/2 being rejected doesn't mean you can't have it.
    What it *does* mean is that the present situation, where some Prologs
    can solve length(X, 3) and some can't, is considered quite acceptable
    by the committee.

[3] The omission of nl/0 means that BSI Prolog has no portable way of
    ending an output record.  The end-of-line character is 31 in
    DEC-10 Prolog, 10 in UNIX versions of Quintus Prolog, 13 in Xerox
    Quintus Prolog, and I not only haven't the foggiest notion what it
    is in the /370 port of Quintus Prolog, I don't need to know.  In a
    record-oriented system, the very notion of an end-of-line character
    makes little sense, but nl/0 does!

    As an aside, as far as I am concerned one of the more serious
    defects of DEC-10 Prolog considered as a candidate for a standard
    is that it wouldn't cope well with record-oriented systems such as
    IBM's VM/CMS.  The BSI group appears to have made no attempt to
    remedy this, and as evidenced by [1], they don't seem to realise
    that there is any problem.

[4] Ok, the "see and tell" family was not the clearest, and streams such
    as C or Common Lisp (or even ADA) provide are a much better idea.
    But if you want to write portable code at the moment, you have to
    use them.  Can they be implemented using the streams facility that
    BSI Prolog offers?  As it happens, they CAN'T.  They can be modelled
    faithfully using streams in Quintus Prolog or Arity/Prolog.  Speaking
    from our experience at Quintus, getting the details right was
    surprisingly tricky.  Not hard, there were just a lot of corners to
    watch out for.  The BSI committee's choice means that vendors will
    continue to provide the "see and tell" family for backwards
    compatibility, but will continue to do it with variations.

    The streams provided in BSI Prolog are more like Fortran channels
    than like C streams:  that is, a stream identifier is an atom that
    the programmer assigns.  This means that it is impossible to write
    a library package which opens streams in such a way that it will
    never interfere with its user's streams.

[5] The omission of keysort/2 is rather surprising.  Recall that keysort/2
    sorts a list of Key-Datum pairs stably, ignoring the Data.  What does
    it do if one of the list elements has some other form?  We've already
    seen one otherwise excellent Prolog use an unstable sort for keysort/2
    (a "quick"-sort was used for speed, the irony is that it was SLOWER).
    This is the kind of thing a standard should address, but the BSI 
    committee are content to leave this up to the vendor's imagination.

    Of course, it's clear why they've dropped keysort/2:  BSI Prolog does
    not include bagof/3.  What it has is findall/3.  Only the name is
    different.

    The text of PS/230 says of sort/2 in section 15.3
	NOTE: this predicate has a misleading name		--HUH?
	and effect.						--EH WHAT?
	It exists almost entirely because it is required
	in the implementation of set/3.				--MAYBE.
	It seems unnecessary for the Prolog standard.
    How can a predicate have a misleading effect?  sort/2 sorts, how is
    that a misleading name?  (Mind you, it might have been better
    called sort_list/2.)

    This paragraph is, to my mind, conclusive proof that at least one
    person in the BSI committee has no idea of how to write efficient
    Prolog code.  I keep finding that sort/2 makes the difference
    between an O(N*N) and an O(N*lgN) algorithm, and I cannot be
    indifferent to that.  sort/2 and keysort/2 are of the utmost
    practical importance.

    But still, they provide @< (but NOT compare/3!), so one can
    implement sort/2 if one wishes.  Is that a good reason for leaving
    it out?  Well, if it is easy to implement, maybe it's ok to leave
    it out.  But PS/230 provides good evidence that it isn't as easy
    as I thought.  Here's their code:

	?- mode(sort(+,?)).		% NB!

	sort([], []).
	sort([X|T], [K|R]) :-
		smallest([X|T], K),
		remove(K, [X|T], Rest),
		sort(Rest, R).

	smallest([H|T], H) :-
		less_than_all(H, T), !.
	smallest([H|T], K) :-
		smallest(T, K).

	less_than_all(H, []).
	less_than_all(H, [N|L]) :-
		H @< N,
		less_than_all(H, L).

	remove(_, [], []).
	remove(K, [H|T], L) :-
		K == H, !,
		remove(K, T, L).
	remove(K, [H|T], [H|L]) :-
		remove(K, T, L).

    Now, the fact that this has cubic worst-case time is beside the point.
    It is only meant as a specification.  But how can I have any
    confidence in the work of a standards committee whose official
    definition of sort/2 has the property that the query
	?- sort([a,b,c], [c,b,a]).
    succeeds?  The mode declaration explicitly permits such queries!

    It should come as no surprise that the official BSI definition of
    findall/3 (oops, sorry, that's a not-invented-here name, the real
    official BSI name is bag/3) has a similar bug.  I've pointed out
    bugs in findall/3 enough times not to bore you with this one, it's
    an old friend.

[6] There are built-in predicates atom/1, atomic/1, integer/1, real/1 &c.
    Fine, except that they don't do what other Prolog systems have them do.
    atom(X) must, in BSI Prolog, signal an error if X is a variable.

    Now this *would* have been a sensible idea back when Prolog was first
    being defined, but a change of this magnitude is quite out of place
    when you are standardising a language that already exists.

    My objection is not to there being built-in predicates with such an
    effect, but to using for them names that are already in use by most
    Prologs to mean something else.

Compared with the description of the built-in predicates, the grimoire
is a miracle of clarity and good sense.

Mich Meier says
>       My global impression from BSI is, I'm afraid, close
> 	to that of R.A.O'K, it is a new language, and very
> 	difficult to implement. I've never really understood the grammar
> 	and the 'Formal Specification of Prolog', though :-)
> 
The Formal Specification is rather large.  In fact PS/210 (the Formal
Specification) says on page 15:
	"We need a language larger than Prolog standard."

I have a formal definition which takes about 25 pages.
It was dismissed by the BSI committee as "Pascal-like" (it uses a
functional notation based loosely on ML) and "too hard to read".
PS/120 is 122 pages, excluding indices.  It is one of the sad ironies
of life that the Formal Specification uses notational devices (such as
the infix dot for cons) which the BSI committee has rejected from the
language proper.

A stylistic gripe about the Formal Specification is that the authors
use one-letter variable names for the most part, and while there may
perhaps be a naming convention which makes it all clear, I cannot figure
one out and the text doesn't explain one.

Let me try to make my position on the Formal Specification clear.
Let its merits be as many and as important as they no doubt are.
It will nevertheless be of no use to most people, including most
implementors.  The copy I have is physically heavier than a listing
of C Prolog I have on the same weight of paper.  For the purposes
of a standard, we want a definition which can be used to assist in
making implementations standard.  This means that
  o  it must be simple enough for most implementors to understand
     the whole specification
  o  it must be usable as a comparison; that is, it must be possible
     to produce directly from the definition an implementation which
     is within perhaps a factor of 100 of a "real" implementation,
     so that non-trivial test cases can be run through it

Let's face it, we want the bugs out of the specification BEFORE it is
accepted as a standard.

cdsm@ivax.doc.ic.ac.uk (Chris Moss) (03/23/88)

In article <771@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
cdsm> WRONG. The second is not allowed in the BSI form. You missed the 'h'
rok>
rok>  I jumped to the conclusion that rule 5.5
rok>should have had 'h' as its left-hand constraint because fairly serious
rok>nonsense would result if 5.5 wasn't fixed somehow.

almost right; that clause didn't do what it was intended to do and I've
entirely rephrased in draft 5 (in the post to you).

I feel I should confess to the large number of typos and errors in
the version you received. My only excuse is that most of the work was
done while I was recovering from a car accident and experiencing
quite a lot of back pain.  It's not a good excuse, but it's the only
one I have! For the same reason I didn't run that version through
Prolog, tho others had applied the treatment to earlier versions.

rok>Well, it depends what you mean by a symbol.  I regard "fred(" or ":-("
rok>as a single token.  It seems just as reasonable to do that as to regard
rok>"1.0e-4" as a single token, or do you want to allow spaces there too?

An intriguing viewpoint. Unfortunately not backed by the published
grammar for Quintus (manual version 10, release 2.0). May I quote:

term(0) --> functor ( arguments )
              {provided there is no space between functor and the '('}

functor --> name
   etc.

Nowhere in the definition of "name" does "(" appear.  I suggest you get
Quintus to modify their grammar to fit in with your views.  Incidentally,
the section on "Syntax of Tokens as character strings" in the Quintus
manual is even more imprecise. The only mention of '(' is in the
production:

punctuation-char --> () | [] | {} | , | |

which, if I can possibly understand it (the use of bold characters in the
manual is rather inconsistent), means that brackets can only be used in a
Prolog program if paired with no characters inbetween!

rok>Putting a space after a left parenthesis or before a right parenthesis
rok>is appallingly bad English punctuation, so it sounds as though you must
rok>have a lot of trouble with your typists working on English too.

touche!

rok>Do you regard the fact that a typist is likely to mistake an iota for
rok>an i or an epsilon for an e as an argument that mathematiciains should
rok>not use Greek letters?  Should we outlaw vertical bars because bad
rok>typists think they are solidii or ells or capital Is?  

I think you're getting away from the point -- tho in the standard we DO
allow other Europeans to use their alphabetic characters with diacritical
marks.

rok>  Surely it is inconsistent to argue that
rok>	"RED O" and "REDO"
rok>are different, and that is a Good Thing, but
rok>	"red (O)" and "red(O)"
rok>being different is a Bad Thing?  Blanks are being treated as
rok>significant in both cases. 

Oh dear, you don't really mean this do you Richard?

rok>The only constraint is that if <atom> is a prefix operator, there must
rok>be no space between <atom> and "(".  Therefore :-(p,q) ***IS*** in the
rok>grammar.

agreed. In version 5 we have reluctantly invented the new category of
"reserved graphic symbol" which includes all the system operators and not
just ".". One can still get at the atomic symbols by quoting.

rok> The grimoire makes it plain that
rok> 	A , B
rok> and	A & B		<--- BIG MISTAKE
rok> are both mapped to sys(and,[A,B]), but whether either of these is the
rok> same as ','(A,B) or '&'(A,B) is not said.  
cdsm> 
cdsm> The only context in which they are the same is when they are passed to
cdsm> 'call' or another meta-primitive which maps terms to predicates.
rok>
rok>No, the grimoire says very very clearly that both (a,b) and (a&b)
rok>are mapped to the same Abstract, namely
rok>
rok>	sys(and, [func(a,[]), func(b,[])])
rok>

   I'll say it once, then not again. Richard I CAN'T STAND your upper class
   British accent! If I were you I wouldn't advertise it! :-)

You've made the point in another message I haven't had time to reply to
yet. The grammar as you have it ONLY describes clauses. In version 5 we've
provided both -- syntax for clause and for read and semantics for both
states -- actually I think the double semantics is probably an overkill.
The only things it really elucidates are the treatment of constructs such
as if-then-else. So maybe in a future version it'll get toned down.

rok>But the question of which symbols the programmer can declare as operators
rok>is surely a syntactic question.  If I want to know what operators I can
rok>declare in Algol 68, I look in the grammar.  

Agreed, and it is possible in the revision. Incidentally once upon a time
I liked Algol 68 too! My Ph.D. thesis contains a restatement of syntax and
semantics of a largish subset of the language in DCG form.

cdsm> Do people want: (3) the full freedom to use logical symbols or
cdsm> natural language symbols as they think fit?
rok>
rok>Everyone will go for (3), of course.  But that is something of a red
rok>herring, as BSI Prolog won't allow it.  Sure I'd like to be able to
rok>write
rok>	every group is a monoid.
rok>Oh, "natural language symbols" didn't mean that?  Silly me.

I think what I meant was obvious from context. One of the delights of
conversing in English not Prolog!

rok>This applies to the rules proper only.  It does not apply to the lines
rok>labelled "Constraint", "Abstract", "Priority", "Input", "Output".
rok>There are at least two problems with these additional lines.
rok>
rok>The first, of course, is that they use a two-dimensional format where
rok>the number of spaces is vitally significant:

Actually, it very rarely uses spaces - usually tabs! :-)

rok>One also has to watch out for the fact that some lines are omitted from
rok>some rules.  I believe it to be the case that to determine which attributes
rok>are relevant to what non-terminals it is necessary to examine the entire
rok>grammar.  

I took your suggestion of converting it directly to DCG form, and I hope
it is true now that no attributes are omitted. It should NOT be necessary.

rok>But the second, and biggest problem, is that not only are these new lines
rok>not part of BS6154, the whole thing is a new formalism which is not
rok>described in any of the documents that the BSI committee have sent me.

It IS described in the document itself. Admittedly only in English!

rok>What does it mean when a rule of the grimoire says
rok>
rok>Rule	 foo = 	baz,  [ ugh ] ;
rok>Abstract f(X,Y)	X	Y
rok>
rok>I *think* it means
rok>
rok>	 foo =	baz, ugh ;
rok>	 f(X,Y)  X    Y
rok>+
rok>	 foo =   baz ;
rok>	 f(X,[])
rok>
rok>but I can find nothing that says so.  

Correct; this IS in the current draft, together with the rest.

So much for now.
Chris Moss.

ok@quintus.UUCP (Richard A. O'Keefe) (03/25/88)

In article <239@gould.doc.ic.ac.uk>, cdsm@ivax.doc.ic.ac.uk (Chris Moss) writes:
> I feel I should confess to the large number of typos and errors in
> the version you received. My only excuse is that most of the work was
> done while I was recovering from a car accident and experiencing
> quite a lot of back pain.

I'm sorry to hear this, and hope that you are recovered.
Would it be appropriate to mark some of the documents "not for review"?
It didn't seem to me that the "Feb 88" document had significantly more
problems than the "February 88" one.

> rok>Well, it depends what you mean by a symbol.  I regard "fred(" or ":-("
> rok>as a single token.  It seems just as reasonable to do that as to regard
> rok>"1.0e-4" as a single token, or do you want to allow spaces there too?

> An intriguing viewpoint. Unfortunately not backed by the published
> grammar for Quintus (manual version 10, release 2.0). May I quote:

I said that __I__ regard "fred(" as a single token.
I did *not* say that __Quintus__ share this point of view.
I have been pushing this view since 1983.

Presumably everyone reading this newsgroup has read the document
"How to Use Usenet" (there is a package of such documents broadcast
in news.<something or other> every couple of months; your news
administrator should be able to provide you with a copy, it's also
part of the documentation set which comes with the B news sources).
Every message in this or any other newsgroup comes with an implicit
disclaimer:  the views of the poster are not to be taken as the views
of his organisation.  My views are not necessarily the views of Quintus.
What Quintus see fit to put in a manual is not necessarily something I
like, agree with, or even know about.  Nor do I have the power to make
Quintus put anything I might happen to want or like into the language
or the manuals.

> rok>Do you regard the fact that a typist is likely to mistake an iota for
> rok>an i or an epsilon for an e as an argument that mathematiciains should
> rok>not use Greek letters?  Should we outlaw vertical bars because bad
> rok>typists think they are solidii or ells or capital Is?  

> I think you're getting away from the point -- tho in the standard we DO
> allow other Europeans to use their alphabetic characters with diacritical
> marks.

What other Europenas may use was not the point.  The original claim was
that because typists sometimes mistake "fred(" for "fred (" the blank
should be allowed, and I was rebutting that by pointing out that we do
not allow such mistakes to forbid other useful typographical practices.
In fact it *has* been proposed in all seriousness (CACM, early 70s) that
programming languages should treat 0 and O in identifiers as identical.

> rok>  Surely it is inconsistent to argue that
> rok>	"RED O" and "REDO"
> rok>are different, and that is a Good Thing, but
> rok>	"red (O)" and "red(O)"
> rok>being different is a Bad Thing?  Blanks are being treated as
> rok>significant in both cases. 

> Oh dear, you don't really mean this do you Richard?

Yes I do.  Whyever not?  Where does the analogy break down?
The BSI grimoire treats "f-1" and "f -1" differently, after all.

>    I'll say it once, then not again. Richard I CAN'T STAND your upper class
>    British accent! If I were you I wouldn't advertise it! :-)

Pardon?  I haven't got any sort of British accent.  No Aotearoa ahau!
And I don't see the relevance of my accent to a discussion of Prolog syntax.

> You've made the point in another message I haven't had time to reply to
> yet. The grammar as you have it ONLY describes clauses. In version 5 we've
> provided both -- syntax for clause and for read and semantics for both
> states -- actually I think the double semantics is probably an overkill.
> The only things it really elucidates are the treatment of constructs such
> as if-then-else. So maybe in a future version it'll get toned down.

Look, for the purpose of explaining how things like
	read(X), call(X)
work, the BSI standard must include in some fashion a mapping from
terms-qua-terms to terms-qua-code.  Why not simply specify the grammar
of terms-qua-terms, and define the meaning of terms-qua-code as the
image of the term reading under the term-to-code map?

> rok>But the second, and biggest problem, is that not only are these new lines
> rok>not part of BS6154, the whole thing is a new formalism which is not
> rok>described in any of the documents that the BSI committee have sent me.

> It IS described in the document itself. Admittedly only in English!

No, the document I have seen merely says (incompletely) what the formalism
LOOKS like.  There was nothing to say what it MEANS, not in any language.
What the document said was "Each entry should be considered as a parameter
of a logic grammar (i.e. a definite clause or metamorphosis grammar)."
It didn't say how the correspondence is to be realised, which means that
the treatment of [optional] and {repeated} items was left completely
unclear.  Neither is it explained what -exceptions with "facets" mean,
but that's ok because only the lexical rules use -exceptions and they
haven't any facets.

kers@otter.hple.hp.com (Christopher Dollin) (03/25/88)

"cdsm@ivax.doc.ic.ac.uk (Chris Moss)" says:

|   I'll say it once, then not again. Richard I CAN'T STAND your upper class
|   British accent! If I were you I wouldn't advertise it! :-)

Chris, *I* hadn't noticed an "upper class British accent" in Richard's
postings. He doesn't write in a way I wouldn't write myself (but he's better
at it that I would be) and upper class I am not! Perhaps you have auditory
evidence denied to the net? (I encountered Richard once, but it was in a 
previous experience and I can't remember his voice.)

What is the word for the "accent" of writing?


Regards,
Kers                                    | "Why Lisp if you can talk Poperly?"

jeff@aiva.ed.ac.uk (Jeff Dalton) (03/29/88)

>"cdsm@ivax.doc.ic.ac.uk (Chris Moss)" says:

>   I'll say it once, then not again. Richard I CAN'T STAND your upper class
>   British accent! If I were you I wouldn't advertise it! :-)

There are occasions where the accent is very, very obvious.  Whether is
is properly upper class is another matter.

-- Jeff

fritz@hpfclp.HP.COM (Gary Fritz) (03/31/88)

> "jeff@aiva.ed.ac.uk (Jeff Dalton)" says:
> 
> >"cdsm@ivax.doc.ic.ac.uk (Chris Moss)" says:
> 
> >   I'll say it once, then not again. Richard I CAN'T STAND your upper class
> >   British accent! If I were you I wouldn't advertise it! :-)
> 
> There are occasions where the accent is very, very obvious.  Whether is
> is properly upper class is another matter.

Whether Richard's accent (upper-class British or middle-class Turkistani)
is germane to his discussion is yet another question.  And I think we all
know the answer.

Gary Fritz