[comp.databases] Quel vs SQL in Ingres 5.0

mohan@ihlpf.ATT.COM (Mohan Palat) (04/09/88)

		SQL vs QUEL in Ingres 5.0
		-------------------------

	In Ingres 5.0, all SQL queries are converted to QUEL and then
	handled in the usual manner. Hence, there is no performance
	advantage in using SQL over QUEL, in an Ingres 5.0 application.
	Is this true?
	Apart from performance, is there any significant (dis)advantage
	in using QUEL/SQL in Ingres 5.0?

	Mohan Palat (ihlpf!mohan)
-- 
MOHAN PALAT

larry@postgres.uucp (Larry Rowe) (04/09/88)

There is a performance penalty to using SQL in INGRES 5.0 -- the time
to translate from SQL to QUEL.  This time is negligable for most
applications, but it may be noticable in high xact rate applications
where the xacts are one-table queries.  The reason is that a one-table
query ought to take 50-100 msecs on a VAX 780 class machine.  The extra
translation probably takes 5 msecs so it can slow things down by 5-10%.

This issue is moot with INGRES 6.0 which has a native SQL parser in the
backend.  I believe 6.0 is in beta release now and is expected to be
released for production use shortly.  Check with your RTI sales rep.
	larry

jkrueger@daitc.ARPA (Jonathan Krueger) (04/10/88)

In article <2239@pasteur.Berkeley.Edu> larry@postgres.UUCP (Larry Rowe) writes:
>[in INGRES 5.0 it may take up to 10% longer to execute an SQL query,
>notably where the xacts are one-table queries, because it translates
>the SQL to QUEL.]

Our experience confirms this, usually the difference is too small to
measure.  To get an idea of how little the component of translation
contributes to the total cost of a query, try "set printqry" in your
sql terminal monitor session, this will type out the translated QUEL
and then execute the query as usual.  This is also a fun way to learn
QUEL if you know SQL.

However, two problem areas remain.

First, ABF translates SQL to EQUEL at compile time.  This is a good
thing because it removes runtime translation overhead.  But it requires
an additional pass and an additional file for each ABF frame.  Worse,
it introduces limitations on OSL/SQL, such as lack of full SQL
functionality while in OSL, and serious bugs in the OSL to ESQL/C
interface.  I think their SQL parser's ability to detect errors is also
less developed than QUEL's, leading to errors discovered at the EQUEL
or C pass, whose error messages are tougher to relate to your OSL
source.

>This issue is moot with INGRES 6.0 which has a native SQL parser in the
>backend.  I believe 6.0 is in beta release now and is expected to be
>released for production use shortly.  Check with your RTI sales rep.

Our sales rep says version 6.0 arrives on Unix before 1989, but not
much before, and only on Sun and Ultrix.  Other Unix machines, such as
ours, get it some unspecified period after that.  When we see it we'll
compare it with what other vendors have available by that time.

Second, SQL as we know it is less general than QUEL.  For instance, if
you need to update a table from another table, you may pay a
substantial performance penalty in SQL versus QUEL.  You may also pay a
penalty of increased programmer errors and lower productivity.  I don't
know how RTI can fix this and still call it SQL. At least they do offer
you a choice.

-- Jon Krueger

...uunet!daitc!jkrueger
jkrueger@daitc.arpa

pavlov@hscfvax.harvard.edu (G.Pavlov) (04/11/88)

In article <4350@ihlpf.ATT.COM>, mohan@ihlpf.ATT.COM (Mohan Palat) writes:
> 		SQL vs QUEL in Ingres 5.0
> 		-------------------------
> 	In Ingres 5.0, all SQL queries are converted to QUEL and then
> 	handled in the usual manner. Hence, there is no performance
> 	advantage in using SQL over QUEL, in an Ingres 5.0 application.
> 	Is this true?
> 	Apart from performance, is there any significant (dis)advantage
> 	in using QUEL/SQL in Ingres 5.0?

  I don't know if anyone chooses SQL over anything else because of performance,
  tho there are several DBMS vendors out there who will try to convince you
  that there is a relationship between the two.

  I can offer three "answers" to your two questions:

   1. RTI will be releasing version 6 in the upcoming months (staggered release;
      VMS first).  In version 6, SQL will run in native mode.

   2. The main reason SQL is this year's "hot" solution is that it is expected 
      to become the "standard" for relational dbms query and the majority of 
      major dbms vendors that I know of either have added SQL or are in the 
      process of doing so.  In many cases (RTI, for example), this has been for
      marketing reasons, pure and simple. 

      Using SQL is supposed to guarantee a site long-term portability - e.g., 
      move your db to another machine & dbms with less pain if your present one
      goes under, fails to port to your preferred hardware platform, etc.  Or,
      you wish to distribute your workload between mini/mainframes and pc's,
      and you are forced into running different dbms's on each category of 
      machine. 

      My own view on the SQL portability issue is:

      a. the portability issue is overexaggerated.  SQL is not a language per
         se and covers only a subset of the total set of operations that a dba
         or systems administrator must perform.  Also, there is no consistency
         in call syntax from HLI's.  Some use preprocessors to convert embedded
         statements, others simply provide a set of subroutines; some require
         alignment on word boundaries, others don't, etc.
 
      b. having had some experience in porting between totally dissimilar rela-
         tional or pseudo-relational dbms's, I would say that moving from one
         command set to another is not likely to be that much more painful 
         than moving from one SQL-based system to another.  In part this is 
         because one typically is performing a very limited set of dbms mani-
         pulations in an HLI-based program and the number of lines of code that
         must be changed (or, even, changed substantially) is not that large.
         And operations such as screen manipulation must be largely done out-
         side of command sets such as SQL anyway.

      c. I expect that the majority of the major dbms vendors will ultimately
         provide "gateways" between their systems and other "best sellers" -
         which will be reasonably transparent, such as RTI's current QUEL->
         SQL conversion.

  3. We use QUEL almost exclusively; we believe it to be more powerful.  How,
     you might ask ?  To be honest, I can't say much, since it has been a long
     time since I have had the privilege of having to use SQL.  But one example
     comes to mind:  during our dbms evalutaion, the following proved to be 
     easy to do in QUEL and a pain in SQL.  I only list the QUEL version, since
     I do not remember what was required from SQL and I do not want to prejud-
     ice it with an overly complex solution.  Maybe someone else can help out.

     Application:  update attribute a1 in table a with attribute b1 in table b,
     wherever the value of a2 in table a is the same as the value of b2 in 
     table b.

     QUEL:

      replace a (a1=b.b1) where a2.a = b2.b


   - In spite of what I said in the above, SQL is probably the safer choice,
     career-wise if nothing else.

     greg pavlov, fstrf, amherst, ny

jkrueger@daitc.ARPA (Jonathan Krueger) (04/12/88)

G.Pavlov writes:
>...My own view is that the [SQL] portability issue is overexaggerated...

Two quotes from C. J. Date's excellent "A Guide to The SQL Standard"
(Addison-Wesley, 1987) seem relevant:

p. 3  "In many ways, the SQL standard is not particularly useful in
itself; it has been characterized, perhaps a little unkindly, as `the
intersection of existing impelmentations,' and as such is severely
deficient in a number of respects...there are some fifty or so SQL
implementations available today, no two of those implementations are
precisely identical, and none of them is precisely identical to
standard SQL!  Even the IBM implementations in SQL/DS and DB2 are not
100 percent compatible with each other, and each of them differs from
System R SQL and also from standard SQL on numerous points of
detail--not all of them trivial, incidentally."

p. 5  "SQL in particular is very far from ideal as a relational
language...in some important respects, it fails to realize the full
potential of the relational model..although there are well-established
principles for the design of formal languages, there is little evidence
that SQL was ever designed in accordance with any such principles.  As
a result, the language is filled with numerous restrictions, ad hoc
constructs, and annoying special rules.  These factors in turn make the
language hard to define, describe, teach, learn, remember, apply, and
implement....Standard SQL leaves as `implementation-defined' certain
aspects that would be much better spelled out as part of the
standard...as a result, it seems likely that every realistic
implementation of the standard will necessarily include many
implementation-defined extensions and variations, and hence that no two
`standard' SQL implementations will ever be truly identical"

aland@infmx.UUCP (Dr. Scump) (04/13/88)

In article <551@hscfvax.harvard.edu>, pavlov@hscfvax.harvard.edu (G.Pavlov) writes:
> 
> 3. We use QUEL almost exclusively; we believe it to be more powerful.  How,
>    you might ask ?  To be honest, I can't say much, since it has been a long
>    time since I have had the privilege of having to use SQL.  But one example
>    comes to mind:  during our dbms evalutaion, the following proved to be 
>    easy to do in QUEL and a pain in SQL.  I only list the QUEL version, since
>    I do not remember what was required from SQL and I do not want to prejud-
>    ice it with an overly complex solution.  Maybe someone else can help out.
>
>    Application:  update attribute a1 in table a with attribute b1 in table b,
>    wherever the value of a2 in table a is the same as the value of b2 in 
>    table b.
> 
>    QUEL:
> 
>     replace a (a1=b.b1) where a2.a = b2.b
                                -----------  Are these correct? Does QUEL
                                             switch to attribute.table
                                             notation for WHERE clauses
                                             instead of table.attribute?
> 
>      greg pavlov, fstrf, amherst, ny
> 

In SQL, this update requires what is known as a Correlated Subquery (since
a subquery is used which correlates the table being updated to value(s) in
some other table).

The equivalent SQL UPDATE syntax:

(I can't remember for sure if the IN clause is Codd or ANSI standard,
so I will give two (equivalent) possibilities for the main WHERE clause.
Either form is acceptable in Informix SQL-based products)

   update a
     set a.a1 = (select b1 from b where a.a2 = b.b2)
     where a.a2 in (select b2 from b)  
or:
   update a
     set a.a1 = (select b1 from b where a.a2 = b.b2)
     where a.a2 = any (select b2 from b)  

The main WHERE clause (applies to the update, not the subquery) may be
omitted if for every value for a2 in table a there exists a b2 in table
b.  If the main WHERE clause is omitted and there are some values for
a2 which do *not* exist in b2, the a1 column for those rows in a are 
set to NULL (thus the potential need for the main WHERE clause).

Say *that* three times fast! :-]


-- 
 Alan S. Denney  |  Informix Software, Inc.  |  {pyramid|uunet}!infmx!aland
    CAUTION: Objects on terminal are closer than they appear...
 Disclaimer: These opinions are mine alone.  If I am caught or killed,
             the secretary will disavow any knowledge of my actions.

pavlov@hscfvax.harvard.edu (G.Pavlov) (04/14/88)

In article <135@infmx.UUCP>, aland@infmx.UUCP (Dr. Scump) writes:
> In article <551@hscfvax.harvard.edu>, pavlov@hscfvax.harvard.edu (G.Pavlov) writes:
> >     replace a (a1=b.b1) where a2.a = b2.b
>                                 -----------  Are these correct? Does QUEL
>                                              switch to attribute.table
>                                              notation for WHERE clauses
>                                              instead of table.attribute?
 Sorry; typed it incorrectly; should be:

        replace a (a1=b.b1) where a.a2 = b.b2

 (see, that is why I need a concise language......)       

   greg pavlov, fstrf, amherst, ny

mitchell@wdl1.UUCP (Jo Mitchell) (04/15/88)

	Well, I dunno about all this chatter.  I used Oracle's DB
	for 2 years and Ingres for the last year.  Practically
	speaking I'm generally in favor of SQL.  Why?
	
	(1) No more range variables.
	(2) Not in.

	Range variables, when used properly are ok:  but I've seen
	countless of disjoint queries like:
		range of p is person
		replace p (address = " ") where person.name = "John"
        MAJOR OOPS.  This never happened in SQL. 

	Something else I miss is the "not in" I use to be able to
	use to check whether corrupted data had made its way into
	a table.  IE, a table is only suppose to have values
	in one column that are stored in another table, or only
	addresses for EXISTING employeess should be stored in the address
	table, etc.  Perhaps someone else knows a quick way in QUEL (tell me),
	but the only way I've heard or seen is:
		retrieve into temptable (realtable.all)
		delete temptable where temptable.value = legaltable.values
		retrieve (nr_val = count(temptable.all))
	(in lieu of 
	   select count(*) from realtable where value not in legaltable.values)

	The thing I do like about INGRES is how powerful its application
	building environment is.  True, the forms and report writer aren't
	too hot.  But a similar application that took me 3 mo. in Oracle
	(using FMS) took 1 week in INGRES! True (again), that power in
	the wrong hands can lead to maintenance nightmares.

	Hurray for 6.0!  (When's it on VMS? :>)

							- Jo

jkrueger@daitc.ARPA (Jonathan Krueger) (04/18/88)

In article <3560011@wdl1.UUCP> mitchell@wdl1.UUCP (Jo Mitchell) writes:
>I've seen countless disjoint queries [in QUEL]...MAJOR OOPS.
>This never happened in SQL. 

I agree, this is a flaw in QUEL.

>	Something else I miss is the "not in" ...
>	   select count(*) from realtable where value not in legaltable.values)

The QUEL syntax is:
	range of r is realtable
	range of l is legaltable
	retrieve (missing = count(r.all
		where any (r.value by l.values where r.value = l.values) = 0))
which I admit is a less intuitive way of expressing a difference operation
than the SQL syntax.

However, QUEL's "any" yields a value that can be used in expressions in an
ordinary way.  For instance,
	retrieve (at_least_one = any(r.all where r.name = "Sam"))
This turns out to be useful in short-circuiting queries.  For instance,
if the column isn't indexed, or if the query defeats indexing:
	retrieve (at_least_one = any(r.all where r.name = "*Sam*"))
the query can return TRUE as soon as it hits the first match, rather
than exhaustively passing through the table.  As implemented in RTI INGRES
5.0, that's exactly what it does.

However, the number of cases where this matters has got to be small.
So I'd say you have two valid criticisms of QUEL.  Since the relational
model doesn't specify the query language syntax for its implementation,
I see little reason not to prefer the better syntax.  It's beyond
argument that better ones than QUEL or SQL exist.  We'll see them in
five or ten or twenty years, depending on how much we cling to existing
ones.

-- Jon

larry@postgres.uucp (Larry Rowe) (04/20/88)

In article <135@infmx.UUCP> aland@infmx.UUCP (Dr. Scump) writes:
>In article <551@hscfvax.harvard.edu>, pavlov@hscfvax.harvard.edu (G.Pavlov) writes:
>> 
>
>In SQL, this update requires what is known as a Correlated Subquery (since
>a subquery is used which correlates the table being updated to value(s) in
>some other table).
>
>The equivalent SQL UPDATE syntax:
>
>   update a
>     set a.a1 = (select b1 from b where a.a2 = b.b2)
>     where a.a2 in (select b2 from b)  
>or:
>   update a
>     set a.a1 = (select b1 from b where a.a2 = b.b2)
>     where a.a2 = any (select b2 from b)  
>
This query is not valid according to the ANSI SQL standard (draft
report) dated Feb 1986.  The syntax for the update statement is

   <update statement: searched> ::=
	UPDATE <table name>
	SET <set clause: searched> [{, <set clause: searched> }]
	WHERE <search condition>

   <set clause: searched> ::=
	<object column: searched> = { <value expression> | NULL }

A <value expression> is a computed value that may contain constants,
references to other columns in the table being updated, or functions
of these values.

The feature you are using in INFORMIX SQL is a good one.  It should be
in every implementation of SQL and it should be added to the standard.
But today, at least as far as I can read it, it is not part of the
standard.  The reason is because of the direct update of tuples
implementation used in System-R.  You have to disallow references
to another table to avoid the halloween problem.
	larry