View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Mike Elston
    4                   Matt Lilley
    5    E-mail:        matt.s.lilley@gmail.com
    6    WWW:           http://www.swi-prolog.org
    7    Copyright (c)  2014-2015, Mike Elston, Matt Lilley
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36/*  PostgreSQL is a trademark of the PostgreSQL Global Development Group.
   37    Microsoft, SQL Server, and Windows are either registered trademarks or
   38    trademarks of Microsoft Corporation in the United States and/or other
   39    countries. SQLite is a registered trademark of Hipp, Wyrick & Company,
   40    Inc in the United States. All other trademarks or registered trademarks
   41    are the property of their respective owners.
   42*/
   43
   44:-module(cql,
   45         [
   46          cql_execute/1,
   47          cql_error/3,
   48          cql_data_type/10,
   49          cql_get_module_default_schema/2,
   50          cql_goal_expansion/3,
   51          cql_event_notification_table/2,
   52          cql_history_attribute/3,
   53          cql_identity/3,
   54          cql_odbc_select_statement/4,
   55          cql_odbc_state_change_statement/7,
   56          cql_portray/2,
   57          cql_var_check/1,
   58          cql_post_state_change_select_sql/4,
   59          cql_pre_state_change_select_sql/7,
   60          cql_runtime/7,
   61          cql_update_history_hook/14,
   62          cql_set_module_default_schema/1,
   63          cql_show/2,
   64          cql_state_change_statistics_sql/8,
   65          cql_statement_location/2,
   66          cql_temporary_column_name/4,
   67          cql_log/4,
   68          cql_normalize_name/3,
   69          cql_sql_clause/3,
   70          default_schema/1,
   71          odbc_execute_with_statistics/4,
   72          cql_access_token_to_user_id/2,
   73          dbms/2,
   74          odbc_data_type/4,
   75          attribute_domain/4,
   76          database_identity/3,
   77          database_key/5,
   78          primary_key_column_name/3,
   79          statistic_monitored_attribute/3,
   80          domain_database_data_type/2,
   81          database_attribute/8,
   82          database_domain/2,
   83          routine_return_type/3,
   84          database_constraint/4,
   85          in_line_format/4,
   86          row_count/2,
   87          sql_gripe/3,
   88          op(400, xfy, (::)),
   89          op(900, fy,  exists),
   90          op(750, yfx, *==),
   91          op(750, yfx, =*=),
   92          op(750, yfx, ==*),
   93          op(740, yfx, on),
   94          op(700, xfx, =~),
   95          op(700, xfx, \=~),
   96          op(200, fy, #),
   97          op(920, fy, ???),
   98          op(920, fy, ??),
   99          op(920, fy, ?)
  100	  ]).  101
  102:-license(swipl).  103
  104:-use_module(library(chr)).  105:-use_module(library(dcg/basics)).  106:-use_module(library(debug)).  107:-use_module(library(cql/sql_parser)).  108:-use_module(library(cql/sql_tokenizer)).  109:-use_module(library(cql/sql_write)).  110:-use_module(library(cql/sql_keywords)).  111:-use_module(library(cql/cql_database)).  112:-reexport(cql_database, [register_database_connection_details/2,
  113                          cql_transaction/3]).

CQL - Constraint Query Language

Note that CQL is currently in a state of flux. Features may be dropped in future releases, and the generated SQL may change between releases. In particular, runtime mode is deprecated.

CQL is a Prolog interface to SQL databases. There are two modes: fully compiled and runtime. The fully compiled mode should be used if possible due to the far greater compile time checking it provides.

Warnings from CQL

CQL Comparisons with NULL

CQLv2 correctly compiles equality comparisons with NULL into the appropriate expression at runtime. In CQLv1, executing

A={null}, {[A], foo :: [a-A]}

would never succeed, regardless of the value of foo.a. This is no longer the case: If A is {null} then this will execute as SELECT .... WHERE a IS NULL and if A is not {null}, it will execute as SELECT .... WHERE a = ?

See the section Removing null comparisions for the dealing with the common requirement to ignore comparisons with null.

Avoid setof/3 and bagof/3 in CQL queries

It is generally not a good idea to wrap CQL inside a setof/3 or a bagof/3 ... unless you are prepared to declare all the CQL variables that are neither bound nor mentioned in the setof/bagof template. If you want to sort, use findall/3 followed by sort/2. Note that sort/2 (like setof/3) removes duplicates. If you don't want to remove duplicates, use msort/2.

CQL: Retrieved nulls have special logic to handle outer joins

In the course of executing a select query, the following rules are applied:

  1. Any selected attribute that is null does not bind its associated variable.
  2. Just before returning from the query any select variables that are still free are bound to {null}.

This is so we can handle outer joins. Consider this:

x :: [a-A] *== y :: [a-A]

Assume x.a binds A to a non-null value. If there is no matching row in y, then y.a = null. If variable A was truly shared the query could never succeed. By not binding the variable associated with y.a the query can succeed ( rule 1) and A will be bound to the value in x.a.

CQL: Getting Started Quickly

Here is a simple example of a SQL SELECT from the table se_lt_x

test(A) :-
  format('About to call CQL with A=~w', [A]),
  {[],
  se_lt_x :: [a-A,
              b-B,
              c-C]},
  format('B=~w, C=~w', [B, C]).

Comparisons can be done in-line e.g.

[a-'ELSTON_M']

or with the == operator e.g.

[a-A], A == 'ELSTON_M'.

The single = operator means unify, not compare. Use = for unification, not comparison

FIXME: Unification is deprecated.

The operators =:= and \== are also available for numerical value comparisons (they just translate to SQL = and <>, so in fact you could use them for string comparisons)

Debugging CQL queries

You can debug CQL using the meta-predicates ?/1, ??/2 and ???/3:

???{[], se_lt_x :: [a-A, b-_], A == 'ELSTON_M'}.
?/1
Display a summary form of the generated SQL before and after the goal is called.
[main]  CALL   SELECT slx_2.b, slx_2.a  FROM se_lt_x AS slx_2 WHERE slx_2.a = 'ELSTON_M'
[main]  EXIT   SELECT slx_2.b, slx_2.a  FROM se_lt_x AS slx_2 WHERE slx_2.a = 'ELSTON_M' (0.006963s, 0.01cpu, 3,899 inferences)
??/1
Display the exact query (and results) in a format which can be executed directly by the DBMS (In this case, SQL Server) The generated SQL may be significantly more complicated than expected, and this can be used to debug the CQL compiler itself
[main]  CALL
DECLARE @P0 VARCHAR(50);
SET @P0 = 'ELSTON_M';
SELECT slx_450.b,
       slx_450.a
FROM se_lt_x AS slx_450
WHERE slx_450.a = @P0 AND slx_450.a COLLATE Latin1_General_CS_AS = @P0
Result: se_lt_x.b = {null}
        se_lt_x.a = 'ELSTON_M'
 (0.003304s, 0.00cpu, 359 inferences)
???/1
Display simplified SQL before the goal is called and display the results afterwards
[main]  CALL
SELECT slx_450.b,
       slx_450.a
FROM se_lt_x AS slx_450
WHERE slx_450.a = 'ELSTON_M'
Result: se_lt_x.b = {null}
        se_lt_x.a = 'ELSTON_M'
 (0.003304s, 0.00cpu, 359 inferences)

Prolog Variables in CQL queries

A Prolog variable can be simultaneously a SELECT variable, a JOIN variable and a WHERE variable as A is in the following example:

{[],
 se_lt_x :: [a-A, c-C]
 =*=
 se_lt_y :: [d-A, f-F],
 A == 'A4'}

which generates the following SQL

SELECT
  x_192.a, x_192.c, y_73.d, y_73.f
 FROM
  se_lt_x x_192 INNER JOIN se_lt_y y_73 ON y_73.d=x_192.a
 WHERE   x_192.a = ? and y_73.d = ?

Note how all the variables referenced in the query are retrieved in the SELECT. This is done to make the query Prolog-like. This means the retrieved row should behave like a Prolog fact so that when a query succeeds all the variables become instantiated.

There is one notable exception however: WHERE variables and JOIN variables are not bound in aggregation selections

FIXME: Is this still the case?

sum_test :-
  {[],
   #se_lt_x :: [a-ValueA,
                sum(b)-Summation]
   =*=
   #se_lt_y :: [e-ValueB],

   ValueA == ValueB,   % Explicit join point

   group_by([ValueA])},

  writeln(ValueA-ValueB-Summation).
'ELSTON_M'-_G375971-99450
true ;

CQL Special Attributes

The following attributes are automatically provided i.e if the attribute is present in the table, CQL will automatically fill in the value:

  1. generation_ Set to 0 on INSERT and incremented by 1 on each update
  2. inserted_ Set to the current time at the time of the INSERT transaction
  3. inserted_by_ Set to the user ID corresponding to the access token supplied to the transaction
  4. updated_ Set to the current time at the time of the UPDATE transaction. Note that updated_ is also set by an INSERT
  5. updated_by_ Set to the user ID corresponding to the access token supplied to the transaction. Note that updated_by_ is also set by an INSERT
  6. transaction_id_ Set to the transaction ID

All the special attributes can be overridden by supplying the attribute-value pair explicitly.

CQL Examples

Rather than provide an abstract description of CQL syntax here is a set of examples that show how to use it.

CQL Simple INSERT

{[],
 insert(se_lt_x, [a-'A', b-'B', c-100])}

CQL Simple INSERT with retrieval of identity of the inserted

{[],
 insert(se_lt_x, [a-'A', b-'B', c-100]),
 identity(I)}

CQL Simple DELETE

{[],
 delete(se_lt_x, [x_pk-I])}

Note that the WHERE clause is part of the delete/2 term unlike update where the WHERE clause is defined outside the update/2 term. I could have made delete consisent with update, but this would have required the @ alias in the delete WHERE clause to identify the table where the rows are to be deleted). This seems like overkill because a delete can in fact refer to only one table anyway i.e. you can't identify rows to delete via a JOIN.

CQL Simple SELECT

{[],
 se_lt_x :: [a-A, b-B]}

This query will either:

CQL Simple UPDATE

{[],
 update(se_lt_x, [c-100]),
 @ :: [a-'A1'],
 row_count(N)}

This corresponds to UPDATE se_lt_x SET c=100 WHERE se_lt_x.a='A1'. The '@' is a special alias referring to the table that is being updated. The row_count/1 term gives the number or rows updated.

CQL WHERE with arithmetic comparison

{[],
 se_lt_x :: [a-A, c-C],
 C > 10}

CQL Simple INNER JOIN

{[],
 se_lt_x :: [a-J1, c-C]
  =*=
 se_lt_y :: [d-J1, f-F]}

The join is se_lt_x.a = se_lt_y.d because of the shared variable J1. se_lt_x.c will be returned in C and se_lt_y.f will be returned in F

CQL Arithmetic UPDATE with an INNER JOIN and a WHERE restriction

{[],
 update(se_lt_x, [c-(C + 2 * F + 20)]),
 @ :: [a-A, c-C] =*= se_lt_y :: [d-A, f-F],
 C < 100}

This joins the table being updated (table se_lt_x) on table se_lt_y where se_lt_x.a = se_lt_y.a and where se_lt_x.c < 200 then updates each identified row se_lt_x.c with the specified expression.

CQL: Confirm row does not exist

\+ exists {[], se_lt_x :: [a-'Z']}

CQL: Aggregation - Count

{[],
 se_lt_x :: [count(c)-C]}

This will count the rows in table se_lt_x

CQL: Aggregation - Sum

{[],
 se_lt_x :: [sum(c)-C]}

Sum the values of attribute c in table se_lt_x

CQL: Aggregation - Average

{[],
 se_lt_x :: [avg(c)-C]}

Calculate the mean of the values of attribute c in table se_lt_x

CQL: Maximum Value

{[],
 se_lt_x :: [max(c)-C]}

Calculate the maximum of the values of attribute c in table se_lt_x

CQL: Minimum Value

{[],
 se_lt_x :: [min(c)-C]}

Calculate the minimum of the values of attribute c in table se_lt_x

CQL: Aggregation requiring GROUP BY

{[],
 se_lt_z :: [g-G, sum(i)-I],
 group_by([G])}

This will generate the GROUP BY SQL and sum se_lt_z.i for each value of se_lt_z.g

CQL: INNER JOIN with an aggregation sub-query where the sub-query is constrained by a shared variable from the main query

{[],
 se_lt_x :: [b-J1, a-A]
   =*=
 se_lt_z :: [h-J1, i-I, g-Z],
 I > min(Y, se_lt_y :: [f-Y, d-Z])}

The main query and the sub-query share variable Z. The generated SQL is:

SELECT
  x37.a, z4.i, z4.g
 FROM
  se_lt_x x37 INNER JOIN se_lt_z z4 ON x37.b=z4.h and z4.h=x37.b
 WHERE
  z4.i > (SELECT min(y11.f) FROM se_lt_y y11 WHERE z4.g=y11.d)

CQL: INNER JOIN in an aggregation sub-query

{[],
 se_lt_y :: [d-D,f-F],
 F < sum(I,
         se_lt_x :: [b-J1]
           =*=
         se_lt_z :: [h-J1, i-I])}

CQL: Negation

{[],
 se_lt_x :: [a-A, b-B],
 \+ exists se_lt_y :: [d-A]}

The generated SQL is:

SELECT
  x39.a, x39.b
 FROM
  se_lt_x x39
 WHERE NOT EXISTS (SELECT * FROM se_lt_y y13 WHERE x39.a = y13.d)

CQL: EXISTS

An exists restriction translates to a WHERE sub-query and is used to say that "each row returned in the main query must satisfy some condition expressed by another query".

Example

{[],
 se_lt_x :: [a-A, b-B],
 exists se_lt_y :: [d-A]}

compiles to:

SELECT
  x.b, x.a
FROM
  se_lt_x x
WHERE
  EXISTS (SELECT * FROM se_lt_y WHERE x.a = y.d)

CQL: Left Outer Join

se_lt_x :: [a-J1, b-B]
  *==
se_lt_y :: [d-J1, e-E]}

CQL: List-based Restrictions

CQL supports query restrictions based on lists. Note that in both cases \== [] and == [] are equivalent despite the obvious logical inconsistency.

FIXME: Can we make this behaviour be controlled by a flag? It IS quite useful, even if it is completely illogical

{[], se_lt_x :: [a-Bar], Bar == []}

and

{[], se_lt_x :: [a-Bar], Bar \== []}

both do exactly the same thing - they will not restrict the query based on Bar. The second case seems to be logically consistent - all things are not in the empty list.

CQL: Compile time in-list constraint

If your list is bound at compile-time, you can simply use it as the attribute value in CQL, for example:

{[], se_lt_x :: [a-['ELSTON_M', 'LILLEY_N']]}

This does not require the list to be ground, merely bound. For example, this is not precluded:

foo(V1, V2):-
    {[], se_lt_x :: [a-[V1, V2]]}.

If, however, your list is not bound at compile-time, you must wrap the variable in list/1:

Bar = [a,b,c],
{[], se_lt_x :: [bar-list(Bar)]}

If you write

foo(V1):-
    {[], se_lt_x :: [a-V1]}.

and at runtime call foo([value1]), you will get a type error.

Remember: If the list of IN values is empty then no restriction is generated i.e.

{[], se_lt_x :: [a-[], b-B}

is the exactly the same as

{[], se_lt_x :: [b-B}

CQL: Disjunction resulting in OR in WHERE clause

{[],
 se_lt_x :: [a-A, b-B, c-C],
 (C == 10 ; B == 'B2', C < 4)}

The generated SQL is:

SELECT
  x.a, x.b, x.c
 FROM
  se_lt_x x
 WHERE
  ((x.b = ? AND x.c < ?) OR x.c = ?)

CQL: Disjunction resulting in different joins (implemented as a SQL UNION)

{[],
 se_lt_x :: [a-A, c-C]
 =*=
 (se_lt_y :: [d-A] ; se_lt_z :: [g-A])}

The generated SQL is:

SELECT
  x43.c
 FROM
  (se_lt_x x43 INNER JOIN se_lt_z z6 ON x43.a=z6.g AND z6.g=x43.a)

UNION

SELECT
  x44.c
 FROM
  (se_lt_x x44 INNER JOIN se_lt_y y16 ON x44.a=y16.d AND y16.d=x44.a)

CQL: Disjunction resulting in different SELECT attributes (implemented as separate ODBC queries)

{[],
 (se_lt_x :: [a-A, c-10]
 ;
 se_lt_y :: [d-A, f-25])}

The output variable A is bound to the value from two different attributes and so the query is implemented as two separate ODBC queries

CQL: ORDER BY

{[],
 se_lt_z :: [g-G, h-H],
 order_by([-G])}

The order_by specification is a list of "signed" variables. The example above will order by se_lt_z.g descending

CQL: DISTINCT

Use distinct(ListOfVars) to specify which attributes you want to be distinct:

test_distinct :-
  findall(UserName,
          {[],
           se_lt_x :: [a-UserName,
                       c-Key],
           Key >= 7,
           distinct([UserName])},
          L),
  length(L, N),
  format('~w solutions~n', [N]).

CALL  : user:test_distinct/0
26 solutions
EXIT  : user:test_distinct/0 (0.098133s, 0.00cpu, 1,488 inferences)

CQL: SELECT with NOT NULL restriction

{[],
 se_lt_z :: [i-I, j-J],
 J \== {null}}

CQL: First N

{[],
 N = 3,
 se_lt_z :: [i-I],
 top(N),
 order_by([+I])}

This generates a TOP clause in SQL Server, and LIMIT clauses for PostgreSQL and SQLite

CQL: Self JOIN

{[],
 se_lt_z :: [h-H, i-I1]
  =*=
 se_lt_z :: [h-H, i-I2],
 I1 \== I2}

CQL: Removing null comparisions

Use the ignore_if_null wrapper in your CQL to 'filter out' null input values. This is a useful extension for creating user-designed searches.

{[],
 se_lt_x :: [a-UserName,
             b-ignore_if_null(SearchKey),
             ...]}

At runtime, if SearchKey is bound to a value other than {null} then the query will contain WHERE ... b = ?. If, however, SearchKey is bound to {null}, then this comparison will be omitted.

Disjunctions

In general, don't use ignore_if_null in disjunctions. Consider this query:

SearchKey = '%ELSTON%',
{[],
 se_lt_x :: [a-UserName,
             b-RealName],
 ( RealName =~ SearchKey
 ; UserName =~ SearchKey)}

The query means "find a user where the UserName contains ELSTON OR the RealName contain ELSTON". If !SearchKey is {null} then RealName=~ {null} will fail, which is correct. If ignore_if_null was used, the test would succeed, which means the disjunction would always succeed i.e. the query would contain no restriction, which is clearly not the intended result. FIXME: Mike, what is this all about?

CQL: Three table JOIN

{[],
 se_lt_x :: [a-A, c-C]
  =*=
 se_lt_y :: [d-A, f-F]
  =*=
 se_lt_z :: [i-F, g-G]}

The shared variable A joins se_lt_x and se_lt_y; the shared variable F joins se_lt_y and se_lt_z

CQL: Three table JOIN with NOLOCK locking hint

{[],
 se_lt_x :: [a-A, c-C]
  =*=
 #se_lt_y :: [d-A, f-F]
  =*=
 #se_lt_z :: [i-F, g-G]}

The hash operator indicates the table that should be accessed WITH (NOLOCK)

CQL: SELECT with LIKE

{[],
 se_lt_z :: [g-G, i-I],
 G =~ 'A_'}

The operator =~ means LIKE. If you are using PostgreSQL, it means ILIKE.

CQL: Writing exceptions directly to the database

You can write an exception term directly to a varchar-type column in the database. Note that it will be rendered as text using ~p, and truncated if necessary - so you certainly can't read it out again and expect to get an exception! Example code:

catch(process_message(Message),
      Exception,
      {[],
      update(some_table, [status-'ERROR',
                          status_comment-Exception]),
      @ :: [some_table_primary_key-PrimaryKey]}).

FIXME: This code is specific to my usage of CQL

CQL: TOP N is Parametric

You can pass the "N" is TOP N as a parameter (Subject to DBMS compatibility. This works in SQL Server 2005 and later, and PostgreSQL 9 (possibly earlier versions) and SQLite3.

N = 3,
findall(I,
        {[],
         se_lt_z :: [i-I], top(N), order_by([+I])},
        L)

CQL: Using compile_time_goal/1

You can include compile_time_goal(Goal) in your CQL. If you specify a module, it will be used, otherwise the goal will be called in the current module. Note that the goal is executed in-order - if you want to use the bindings in your CQL, you must put the compile_time_goal before them.

Example 1

{[],
 se_lt_x :: [a-UserName,
             b-RealName,
             d-FavouriteColour],
   compile_time_goal(standard_batch_size_for_search(StandardBatchSize)),
   top(StandardBatchSize),
   order_by([+UserName]}

Example 2

excellent_colours(['RED', 'BLUE']).

{[],
 se_lt_x :: [a-UserName,
             b-RealName,
             d-FavouriteColour],
 compile_time_goal(excellent_colours(Colours)),
 FavouriteColour == Colours}

CQL: ON

CQL supports both constant and shared variable join specifications. This is particularly useful when specifying outer joins.

Example

{[],
 se_lt_x :: [a-UserNameA,
             b-RealName,
             d-FavouriteColour]
 *==
 se_lt_x :: [a-UserNameB,
             e-FavouriteFood] on( UserNameA == UserNameB,
                                  FavouriteColour == FavouriteFood,
                                  FavouriteFood == 'ORANGE')}

All the CQL comparison operators, <, =<, ==, =~, \=~, \==, >=, > can be used in ON specifications.

For example:

{[],
 se_lt_z :: [i-J1, k-K]
 *==
 se_lt_x :: [c-J1, a-A, b-B] on A \== 'A1'},

CQL: Expressions In Where Restrictions

Expressions in WHERE restrictions are supported, for example:

{[],
 se_lt_n :: [i-I, j-J, k-K],
 J > 10 * (K / I) + 15},

CQL: Explicitly avoid the "No WHERE restriction" message

To avoid accidentally deleting or updating all rows in a table CQL raises an exception if there is no WHERE restriction.

Sometimes however you really do need to delete or update all rows in a table.

To support this requirement in a disciplined way (and to avoid the creation of "dummy" WHERE restrictions) the keyword absence_of_where_restriction_is_deliberate has been added. For example:

{[],
 update(se_lt_x, [c-10]),
        @ :: [],
        absence_of_where_restriction_is_deliberate}

CQL: HAVING

HAVING restrictions can be specified. For example:

{[],
 se_lt_z :: [sum(i)-I,
             g-G],
 group_by([G]),
 having(I > 30)}

For a description of HAVING see http://en.wikipedia.org/wiki/Having_(SQL)

There is one important difference between SQL HAVING and SQL WHERE clauses. The SQL WHERE clause condition is tested against each and every row of data, while the SQL HAVING clause condition is tested against the groups and/or aggregates specified in the SQL GROUP BY clause and/or the SQL SELECT column list.

CQL: INSERT and UPDATE value in-line formatting

INSERT and UPDATE values can be formatted in-line at runtime. For example:

Suffix = 'NOGG',
cql_transaction(Schema, UserId,
                {[],
                insert(se_lt_x, [a-'A', b-'B', c-100, d-format('EGG_~w', [Suffix])])}),

will insert 'EGG_NOGG' into attribute 'd'.

CQL: Negations in WHERE Clauses

You can specify negations in CQL WHERE clauses e.g.

{[],
 se_lt_z :: [g-G, h-H, i-I],
 \+((G == 'A1', H == 'B1' ; G == 'D1', H == 'B3'))},

Note that, just like in Prolog, \+ is a unary operator hence the "double" brackets in the example above.

CQL: Predicate-generated Attribute Values

It is possible to generate compile time attribute values by specifying a predicate which is executed when the CQL statement is compiled.

The predicate must return the value you want as its last argument. You specify the predicate where you would normally put the attribute value. The predicate is specified with its output argument missing.

Example - Using domain allowed values in a query.

In the following CQL statement the predicate cql_domain_allowed_value/3 is called within findall/3 at compile time to generate a list of domain values that restrict favourite_colour to be 'ORANGE' or 'PINK' or 'BLUE', or 'GREEN'.

colour('ORANGE').
colour('PINK').
colour('BLUE').
colour('GREEN').

{[],
 se_lt_x :: [d-findall(Value,
                       permissible_colour(Value)),
             a-UserName]}

Note how findall/3 is actually called by specifying findall/2.

There is not much point using predicate-generated attribute values in compile-at-runtime CQL as you can always call the predicate to generate the required values outside the CQL statement.

CQL: INSERT from SELECT

INSERT from SELECT is supported:

Constant = 'MIKE',
{[],
 insert(se_lt_x1, [x_pk-Pk, a-A, b-B, c-C, d-Constant]),
 se_lt_x :: [x_pk-Pk, a-A, b-B, c-C, as(d)-Constant]}

which generates the following SQL:

INSERT INTO se_lt_x1 (x_pk, a, b, c, d)
SELECT se_lt_x_955.x_pk, se_lt_x_955.a, se_lt_x_955.b, se_lt_x_955.c, ? AS d
  FROM se_lt_x lt_x_955

Note the use of the as(d) construct in the SELECT part of the CQL to make the constant 'MIKE' appear to come from the SELECT thus setting lt_x1.d to 'MIKE' in every row inserted.

CQL: Hooks

CQL provides a large number of hooks to fine-tune behaviour and allow for customization. These are:

CQL: Generated Code Hooks

CQL: Data Representation Hooks

CQL: Application Integration

CQL: Inline values

cql:cql_inline_domain_value_hook(+DomainName, +Value)
can be defined if you want the given value to be 'inlined' into the CQL (ie not supplied as a parameter). Great care must be taken to avoid SQL injection attacks if this is used.

CQL: Schema

These define the schema. You MUST either define them, or include library(cql/cql_autoschema) and add two directives to build the schema automatically:

Otherwise, you need to define at least default_schema/1 and cql:dbms/2, and then as many of the other facts as needed for your schema.

CQL: Event Processing and History

CQL provides hooks for maintaining detailed history of data in the database.

The hook predicates are:

Event Processing and History recording can be suppressed for a particular update/insert/delete statement by including the _no_state_change_actions_9 directive.

For example

{[],
 update(se_lt_x, [f-'LILAC']
 @ :: [a-'ELSTON_M'],
 no_state_change_actions,   % Don't want history to record this change
 row_count(RowCount)}

CQL: Statistical Hooks

CQL has hooks to enable in-memory statistics to be tracked for database tables. Using this hook, it's possible to monitor the number of rows in a table with a particular value in a particular column.

Often the kind of statistics of interest are 'how many rows in this table are in ERROR' or 'how many in this table are at NEW'? While it may be possible to maintain these directly in any code which updates tables, it can be difficult to ensure all cases are accounted for, and requires developers to remember which attributes are tracked.

To ensure that all (CQL-originated) updates to statuses are captured, it's possible to use the CQL hook system to update them automatically. Define add a fact like:

cql_statistic_monitored_attribute_hook(my_schema, my_table,
                                       my_table_status_column).

This will examine the domain for the column 'my_table_status_column', and generate a statistic for each of my_table::my_table_status_column(xxx), where xxx is each possible allowed value for the domain. Code will be automatically generated to trap updates to this specific column, and maintain the state. This way, if you are interested in the number of rows in my_table which have a status of 'NEW', you can look at my_table::my_table_status_column('NEW'), without having to manage the state directly. CQL update statements which affect the status will automatically maintain the statistics.

The calculations are vastly simpler than the history mechanism, so as to keep performance as high as possible. For inserts, there is no cost to monitoring the table (the insert simply increments the statistic if the transaction completes). For deletes, the delete query is first run as a select, aggregating on the monitored columns to find the number of deletes for each domain allowed value. This means that a delete of millions of rows might requires a select returning only a single row for statistics purposes. For updates, the delete code is run, then the insert calculation is done, multiplied by the number of rows affected by the update.

In all cases, CQL ends up calling cql_statistic_monitored_attribute_change_hook/5, where the last argument is a signed value indicating the number of changes to that particular statistic. */

 1289:-chr_option(line_numbers, on). 1290:-chr_option(check_guard_bindings, error). 1291:-chr_option(debug, off). 1292:-chr_option(optimize, full). 1293:-chr_option(guard_simplification, off). % Added to stop trail overflowing
 1294
 1295:-chr_type list(T) ---> [] ; [T|list(T)]. 1296
 1297:-chr_type 'AggregationOperator' ---> count ; max ; min ; avg ; sum. 1298:-chr_type 'AggregationVariable' == any. 1299:-chr_type 'ApplicationValue' == any. 1300:-chr_type 'DebugMode' ---> explicit. 1301:-chr_type 'DictinctionType' ---> no_distinction ; distinct_on_specified_attributes ; distinct_on_all_select_attributes. 1302:-chr_type 'Dsn' == any. 1303:-chr_type 'Attribute' ---> attribute('Schema', 'TableAlias', 'AttributeName'). 1304:-chr_type 'AttributeName' == any. 1305:-chr_type 'AttributeNameValuePair' ---> 'AttributeName'-'ApplicationValue'. 1306:-chr_type 'BooleanOperator' ---> and ; or. 1307:-chr_type 'ComparisonOperator' ---> < ; =< ; == ; \== ; >= ; > ; (=~) ; (=\=) ; (=:=). 1308:-chr_type 'CompilationInstruction' ---> if_var('Variable') ; if_not_var('Variable') ; if_null('Variable') ; if_not_null('Variable') ; list('Variable') ; empty('Variable') ; not_empty('Variable') ; compile ; and('CompilationInstruction', 'CompilationInstruction'). 1309:-chr_type 'CompileMode' ---> runtime ; compiletime. 1310:-chr_type 'ConjunctionGoal' == any. 1311:-chr_type 'ConjunctionVariable' == any. 1312:-chr_type 'Connection' == any. 1313:-chr_type 'Constraints' == any. 1314:-chr_type 'ClockTime' == any. 1315:-chr_type 'CpuTime' == any. 1316:-chr_type 'Cql' == any. 1317:-chr_type 'Disposition' ---> top ; where ; having ; join. 1318:-chr_type 'EqualityRestrictionVariableUsed' ---> equality_restriction_variable_used. 1319:-chr_type 'Expression' == any. 1320:-chr_type 'ExternalVariable' == any. 1321:-chr_type 'FileName' == any. 1322:-chr_type 'Format' == any. 1323:-chr_type 'FormatArg' == any. 1324:-chr_type 'Goal' == any. 1325:-chr_type 'Having' == any. 1326:-chr_type 'Identity' == int. 1327:-chr_type 'Inferences' == any. 1328:-chr_type 'InputVariable' == 'Variable'. 1329:-chr_type 'Join' == any. 1330:-chr_type 'JoinTreeNode' == any. 1331:-chr_type 'JoinType' ---> 'INNER JOIN' ; 'LEFT OUTER JOIN' ; 'RIGHT OUTER JOIN'. 1332:-chr_type 'Keep' ---> 1. 1333:-chr_type 'LineNumber' == int. 1334:-chr_type 'N' == int. 1335:-chr_type 'OdbcCachingOption' ---> do_not_cache_odbc_statement ; cache_odbc_statement. 1336:-chr_type 'OdbcDataType' ---> varchar(int) ; decimal(int, int) ; timestamp ; integer ; bit. 1337:-chr_type 'LogicalType' ---> varchar ; decimal ; timestamp ; integer ; boolean. 1338:-chr_type 'OdbcInput' == any. 1339:-chr_type 'OdbcOutput' == any. 1340:-chr_type 'OdbcParameter' ---> odbc_parameter('Schema', 'TableName', 'AttributeName', 'ApplicationValue', 'OdbcParameterUse', 'OdbcDataType')   % OdbcDataType unbound if no override required
 1341                              ; odbc_explicit_type_parameter('OdbcDataType', 'ApplicationValue', 'OdbcParameterUse'). 1342:-chr_type 'OdbcParameterUse' ---> insert_value ; update_value ; evaluated_update_attribute ; evaluated_update_parameter ; where_value ; top_value. 1343:-chr_type 'On' == any. 1344:-chr_type 'OrderBy' ---> +('Variable') ; -('Variable'). 1345:-chr_type 'Output' ---> output('Schema', 'TableName', 'AttributeName', 'Variable') ;
 1346                         ignore_output ;
 1347                         count('Variable') ;
 1348                         avg('Variable') ;  % PostgreSQL
 1349                         selection_constant('Schema', 'TableName', 'AttributeName', 'Variable'). 1350:-chr_type 'Phase' ---> initial ; distinct ; top ; select_attributes ; from ; where ; group_by ; having ; order_by ; union ; limit. 1351:-chr_type 'PreparedStatement' == any. 1352:-chr_type 'PrimaryKeyAttributeName' == 'AttributeName'. 1353:-chr_type 'PrimaryKeyValue' == any. 1354:-chr_type 'QueryId' == any. 1355:-chr_type 'QueryLevel' ---> top_level_query ; sub_query. 1356:-chr_type 'Reason' == any. 1357:-chr_type 'ResultSpec' == any. 1358:-chr_type 'Resolved' ---> resolved. 1359:-chr_type 'RestrictionExpression' == any. 1360:-chr_type 'RestrictionType' ---> where ; having ; join. 1361:-chr_type 'RestrictionTree' ---> true ;
 1362                                  comparison('ApplicationValue', 'ComparisonOperator', 'ApplicationValue') ;
 1363                                  sub_query('SubQueryType', list('SqlToken'), 'Tail', list('OdbcParameter')) ;
 1364                                  and('RestrictionTree', 'RestrictionTree') ;
 1365                                  or('RestrictionTree', 'RestrictionTree'). 1366:-chr_type 'Row' == any. 1367:-chr_type 'StateChangeType' ---> insert ; update ; delete. 1368:-chr_type 'QueryType' ---> insert ; update ; delete ; select. 1369:-chr_type 'Schema' == any. 1370:-chr_type 'SelectAttribute' ---> select_attribute('SelectBindingType', 'Schema', 'TableName', 'TableAlias', 'AttributeName'). 1371:-chr_type 'SelectAttributeWithSize' ---> 'Size'-'SelectAttributeInfo'. 1372:-chr_type 'SelectAttributeInfo' ---> select_info('CompilationInstruction', list('SqlToken'), 'Tail', 'Output'). 1373:-chr_type 'SelectAttributeVariableUsed' ---> select_attribute_variable_used. 1374:-chr_type 'SelectBindingType' ---> plain ; aggregation('AggregationOperator'). 1375:-chr_type 'SelectionType' ---> aggregation_selection ; non_aggregation_selection. 1376:-chr_type 'Side' ---> lhs ; rhs. 1377:-chr_type 'Size' == any. 1378:-chr_type 'SqlToken' == any. 1379:-chr_type 'SqlComparisonOperator' ---> < ; <= ; = ; <> ; >= ; > . 1380:-chr_type 'SubQueryType' ---> exists ; \+ . 1381:-chr_type 'Tail' == any. 1382:-chr_type 'TableAlias' == any. 1383:-chr_type 'TableName' == any. 1384:-chr_type 'Variable' == any. 1385:-chr_type 'VariablePair' ---> 'Variable'-'Variable'. 1386:-chr_type 'When' ---> pre_state_change ; post_state_change. 1387
 1388
 1389
 1390:-chr_constraint absence_of_where_restriction_is_deliberate. 1391:-chr_constraint add_on(-'Join', ?'On'). 1392:-chr_constraint aggregation_sub_query(-'QueryId', ?'TableName', ?'TableAlias', ?list('SqlToken'), ?'Tail', ?list('ApplicationValue')). 1393:-chr_constraint aggregation_variable(-'QueryId', +'AggregationOperator', ?'AggregationVariable'). 1394:-chr_constraint attribute_binding(-'QueryId', ?'Attribute', ?'ApplicationValue'). 1395:-chr_constraint attribute_for_group_by(-'QueryId', ?'TableAlias', +'AttributeName', ?'Variable'). 1396:-chr_constraint attribute_for_order_by(-'QueryId', ?'TableAlias', +'AttributeName', ?'Variable'). 1397:-chr_constraint attribute_to_check(+'Schema', +'TableName', ?'AttributeNameValuePair'). 1398:-chr_constraint attributes_to_check(-'QueryId', +'Schema', +'TableName', ?list('AttributeNameValuePair')). 1399:-chr_constraint call_history_hook(-'QueryId', +'Connection'). 1400:-chr_constraint call_row_change_hooks(-'QueryId', +'Connection'). 1401:-chr_constraint check_for_orphan_distincts. 1402:-chr_constraint check_for_orphan_group_bys. 1403:-chr_constraint check_for_orphan_order_bys. 1404:-chr_constraint check_for_orphan_select_attributes_in_aggregations. 1405:-chr_constraint check_for_orphan_select_variables_in_updates. 1406:-chr_constraint check_for_top_without_order_by. 1407:-chr_constraint check_for_unjoined_tables. 1408:-chr_constraint check_query. 1409:-chr_constraint cleanup_compile. 1410:-chr_constraint cleanup_cql_post_state_change_select_sql(-'QueryId'). 1411:-chr_constraint collect_indices(-'QueryId'). 1412:-chr_constraint collect_runtime_constraints(?'Constraints'). 1413:-chr_constraint collect_select_attributes(-'QueryId', +list('SelectAttributeWithSize')). 1414:-chr_constraint comparison(-'QueryId', ?'ApplicationValue', +'ComparisonOperator', ?'ApplicationValue'). 1415:-chr_constraint compile_mode(+'CompileMode'). 1416:-chr_constraint conjunction_constraints(?'Constraints'). 1417:-chr_constraint conjunction_goal(?'ConjunctionGoal'). 1418:-chr_constraint conjunction_variable(-'QueryId', ?'ExternalVariable', ?'ConjunctionVariable'). 1419:-chr_constraint copy_of_from(-'QueryId', ?list('SqlToken'), ?'Tail', ?list('OdbcParameter')). 1420:-chr_constraint find_copy_of_from(-'QueryId', ?list('SqlToken'), ?'Tail', ?list('OdbcParameter')). 1421:-chr_constraint cql2_variable(-'QueryId', -'Variable', ?'RestrictionTree'). 1422:-chr_constraint cql_execute(+'OdbcCachingOption'). 1423:-chr_constraint cql_fully_compiled. 1424:-chr_constraint cql_identity(-'QueryId', +'Schema', ?'Identity'). 1425:-chr_constraint cql_odbc_select_statement(+'Schema', +'SqlToken', ?list('OdbcParameter'), ?list('Output')). 1426:-chr_constraint cql_odbc_state_change_statement(-'QueryId', +'StateChangeType', +'Schema', +'TableName', +'SqlToken', ?list('OdbcParameter'), ?list('Output')). 1427:-chr_constraint cql_post_state_change_select_sql(-'QueryId', +list('AttributeName'), +'OdbcDataType', +'SqlToken'). 1428:-chr_constraint cql_pre_state_change_select_sql(-'QueryId', +'Schema', +'TableName', +'AttributeName', +'SqlToken', +list('AttributeName'), +list('OdbcParameter')). 1429:-chr_constraint cql_state_change_statistics_sql(-'QueryId', +'Schema', +'TableName',  +'StateChangeType', +'SqlToken', +list('AttributeName'), ?list('OdbcParameter'), ?list('OdbcParameter')). 1430:-chr_constraint cql_statement_location(+'FileName', +'LineNumber'). 1431:-chr_constraint create_cql_pre_state_change_select_sql(-'QueryId', +'StateChangeType', +list('SqlToken'), +'TableName', ?list('OdbcParameter')). 1432:-chr_constraint create_cql_state_change_statistics_sql(-'QueryId', +'StateChangeType', +list('SqlToken'), +'TableName', ?list('OdbcParameter')). 1433:-chr_constraint create_in_line_joins. 1434:-chr_constraint create_join_points. 1435:-chr_constraint create_restrictions. 1436:-chr_constraint create_select_bindings. 1437:-chr_constraint debug_after(+'Reason', ?'ResultSpec'). 1438:-chr_constraint debug_before(+'Format', +'Schema', +'FormatArg'). 1439:-chr_constraint debug_statistics(+'CpuTime', +'ClockTime', +'Inferences'). 1440:-chr_constraint delete_row(-'QueryId', +'TableName', ?'TableAlias'). 1441:-chr_constraint determine_select_distinction(-'QueryId'). 1442:-chr_constraint determine_select_distinctions. 1443:-chr_constraint determine_selection_type. 1444:-chr_constraint dictionary_addendum(-'QueryId', ?'ExternalVariable', ?'ConjunctionVariable'). 1445:-chr_constraint dictionary_lookup(-'QueryId', ?'ExternalVariable', ?'ConjunctionVariable'). 1446:-chr_constraint distinct(-'QueryId', -'Variable'). 1447:-chr_constraint distincts(-'QueryId', ?list('Variable')). 1448:-chr_constraint equality_restriction_variable(?'ApplicationValue', ?'EqualityRestrictionVariableUsed'). 1449:-chr_constraint event(-'QueryId'). 1450:-chr_constraint expression_where_restriction_variable(?'Variable'). 1451:-chr_constraint fully_compile. 1452:-chr_constraint generate_sub_query_sql. 1453:-chr_constraint get_conjunction_constraints(?'Constraints'). 1454:-chr_constraint group_by(-'QueryId', -'Variable'). 1455:-chr_constraint group_bys(-'QueryId', ?list('Variable')). 1456:-chr_constraint identify_insert_row(+'StateChangeType', -'QueryId', +'Schema', +'TableName', +'Connection', ?'Identity'). 1457:-chr_constraint identify_post_state_change_values(-'QueryId', +'Connection'). 1458:-chr_constraint identify_pre_state_change_values(-'QueryId', +'StateChangeType', +'Connection'). 1459:-chr_constraint ignore_if_null(?'Variable', ?'Variable'). 1460:-chr_constraint implicit_join(-'QueryId', +'TableAlias', -'QueryId'). % PostgreSQL only
 1461:-chr_constraint implicit_join_link(-'QueryId', -'QueryId'). % PostgreSQL only
 1462:-chr_constraint implicit_join_sql(-'QueryId', ?list('SqlToken'), ?'Tail'). % PostgreSQL only
 1463:-chr_constraint fetch_implicit_join_sql(-'QueryId', ?list('SqlToken'), ?'Tail'). % PostgreSQL only
 1464:-chr_constraint in_line_format(-'QueryId', +'Format', ?list('FormatArg'), ?'ApplicationValue'). 1465:-chr_constraint include_select_attribute(-'QueryId', ?'CompilationInstruction', +'Size', +list('SqlToken'), ?'Tail', ?'Output'). 1466:-chr_constraint insert(-'QueryId', +'Schema', +'TableName', +list('AttributeNameValuePair')). 1467:-chr_constraint instantiate_table_aliases. 1468:-chr_constraint join(-'QueryId', -'Join', -'Join', +'JoinType', -'Join'). 1469:-chr_constraint join_alias(-'Join', +'Side', ?'TableAlias'). 1470:-chr_constraint join_leaf(-'Join', ?'TableAlias'). 1471:-chr_constraint join_on(?'TableAlias', +'AttributeName', ?'TableAlias', +'AttributeName'). 1472:-chr_constraint join_pointer(-'QueryId', -'Join'). 1473:-chr_constraint join_tree_node(-'QueryId', -'Join', +'JoinTreeNode'). 1474:-chr_constraint join_tree_nodes(-'QueryId', +list('JoinTreeNode')). 1475:-chr_constraint join_variable(?'Variable'). 1476:-chr_constraint limit(-'QueryId', +'Schema', +'N'). 1477:-chr_constraint log_select(+'SqlToken', +list('OdbcInput')). 1478:-chr_constraint log_state_change(+'SqlToken', +'StateChangeType', +list('OdbcInput')). 1479:-chr_constraint next_group_by_attribute_needs_comma(-'QueryId'). 1480:-chr_constraint next_in_list_value_needs_comma(-'QueryId'). 1481:-chr_constraint next_order_by_attribute_needs_comma(-'QueryId'). 1482:-chr_constraint no_debug. 1483:-chr_constraint no_sql_statement_generated. 1484:-chr_constraint no_state_change_actions(-'QueryId'). 1485:-chr_constraint no_where_restriction(+'StateChangeType'). 1486:-chr_constraint not_a_singleton(+'Variable'). 1487:-chr_constraint nolock(-'QueryId', ?'TableAlias'). 1488:-chr_constraint number_of_rows_affected(-'QueryId', +'Connection', ?'N'). 1489
 1490:-chr_constraint odbc_select_disjunction(?'Goal'). 1491%:-chr_meta_predicate(odbc_select_disjunction(0)).
 1492
 1493:-chr_constraint odbc_select_statement(+'Schema', +'SqlToken', ?list('OdbcParameter'), ?list('Output')). 1494:-chr_constraint on(-'Join', ?'Resolved', ?'On'). 1495:-chr_constraint order_bys(-'QueryId', ?list('OrderBy')). 1496:-chr_constraint original_cql(?'Cql'). 1497:-chr_constraint original_human_query(?'Cql'). 1498:-chr_constraint outer_side_join(-'Join'). 1499:-chr_constraint phase(-'QueryId', +'Phase'). 1500:-chr_constraint post_execute_cleanup. 1501:-chr_constraint post_state_change_select_statement(-'QueryId', +list('AttributeName'), +'OdbcDataType', +'PreparedStatement'). 1502:-chr_constraint postgres_identity(-'QueryId', ?'Identity'). 1503:-chr_constraint prepare_odbc_statements. 1504:-chr_constraint prior_to_execution. 1505:-chr_constraint query(-'QueryId', +'Schema', +'QueryLevel'). 1506:-chr_constraint query_table_alias(-'QueryId', +'Schema', +'TableName', ?'TableAlias'). 1507:-chr_constraint query_type(-'QueryId', +'QueryType'). 1508:-chr_constraint remove_query(-'QueryId', -'QueryId'). 1509:-chr_constraint resolve_join_points(-'Join', ?'On', ?'On'). 1510:-chr_constraint resolve_join_points. 1511:-chr_constraint restriction_leaf(-'QueryId', +'Disposition', ?'RestrictionTree'). 1512:-chr_constraint restriction_tree(-'QueryId', +'Disposition', ?'RestrictionTree'). 1513:-chr_constraint row_count(-'QueryId', ?'N'). 1514:-chr_constraint runtime_constraints(?'Constraints'). 1515:-chr_constraint search_for_join_aliases(-'Join', +'Side', -'Join'). 1516:-chr_constraint select_attribute(-'QueryId', ?'SelectAttribute', ?'Keep', ?'SelectAttributeVariableUsed', ?'Variable'). 1517:-chr_constraint select_attribute_for_disjunction_comparison(-'QueryId', ?'SelectAttribute'). 1518:-chr_constraint select_attribute_written(-'QueryId'). 1519:-chr_constraint select_attributes_for_disjunction_comparison(-'QueryId', ?list('SelectAttribute')). 1520:-chr_constraint select_binding(-'QueryId', ?'SelectBindingType', ?'Attribute', ?'ApplicationValue'). 1521:-chr_constraint select_distinction(-'QueryId', +'DictinctionType'). 1522:-chr_constraint select_for_insert_variable(-'QueryId', ?'Variable', +'TableName'). 1523:-chr_constraint select_for_insert_variables(?list('Variable'), +'TableName'). 1524:-chr_constraint selection_type(-'QueryId', +'SelectionType'). 1525:-chr_constraint show_debug(+'DebugMode'). 1526:-chr_constraint simplify. 1527:-chr_constraint solve. 1528:-chr_constraint sql_not(-'QueryId', -'QueryId'). 1529:-chr_constraint sql_statement(-'QueryId', +list('SqlToken'), ?'Tail', +list('SqlToken'), ?'Tail', +list('SqlToken'), ?'Tail', ?list('OdbcParameter'), ?list('OdbcParameter'), ?list('Output')). 1530:-chr_constraint state_change_query(-'QueryId', +'StateChangeType', +'Schema', +'TableName'). 1531:-chr_constraint state_change_value(-'QueryId', +'StateChangeType', +'When', +'Schema', +'TableName', +'PrimaryKeyAttributeName', +'PrimaryKeyValue', +'AttributeName', +'OdbcOutput'). 1532:-chr_constraint store_equality_restriction_variables(?list('Variable')). 1533:-chr_constraint store_ignore_if_null_variables(?list('VariablePair')). 1534:-chr_constraint sub_query(-'QueryId', ?list('SqlToken'), ?'Tail', ?list('OdbcParameter')). 1535:-chr_constraint sub_query_join_variable(?'Variable'). 1536:-chr_constraint sub_query_restriction(-'QueryId', +'SubQueryType', ?list('SqlToken'), ?'Tail', ?list('OdbcParameter')). 1537:-chr_constraint sub_query_select(-'QueryId'). 1538:-chr_constraint referenced_table(+'TableName'). 1539:-chr_constraint referenced_tables(?list('TableName')). 1540:-chr_constraint representative_attribute(?'Expression', +'Schema', -'TableName', -'AttributeName'). 1541:-chr_constraint runtime_instantiation_check(-'QueryId', -'Variable'). 1542:-chr_constraint tables_to_remove(+'Schema', +list('Identity')). 1543:-chr_constraint temporary_table(+'Schema', +'Identity'). 1544:-chr_constraint temporary_tables(+'Schema', +list('Identity')). 1545:-chr_constraint top(-'QueryId', +'Schema', +'N'). 1546:-chr_constraint unify(?'Variable', ?'Variable'). 1547:-chr_constraint unify_ignore_if_null_variables. 1548:-chr_constraint union_outputs(-'QueryId', ?list('Output'), ?list('Variable')). 1549:-chr_constraint update(-'QueryId', +'Schema', +'TableName', ?'TableAlias', ?list('AttributeNameValuePair')). 1550:-chr_constraint update_table_alias(-'QueryId', +'Schema', -'Join', ?'TableAlias'). 1551:-chr_constraint update_table_key(-'QueryId', +'Schema', ?list('AttributeNameValuePair')). 1552:-chr_constraint updated_row(-'QueryId', +'StateChangeType', +'When', +'Schema', +'TableName', +'PrimaryKeyAttributeName', +'PrimaryKeyValue', +list('AttributeNameValuePair')). 1553:-chr_constraint updated_row_primary_key(-'QueryId', +'StateChangeType', +'Schema', +'TableName', +'PrimaryKeyAttributeName', +'PrimaryKeyValue'). 1554:-chr_constraint updated_rows(-'QueryId', +'StateChangeType', +'When', +'Schema', +'TableName', +'AttributeName', +list('AttributeName'), +list('Row')). 1555:-chr_constraint variables_to_attributes(?'Expression', ?'Expression'). 1556:-chr_constraint where_restriction_variable(?'Variable'). 1557:-chr_constraint write_expression(-'QueryId', +'Schema', +'TableName', +'AttributeName', ?'TableAlias', ?'Expression'). 1558:-chr_constraint write_group_by_attribute(-'QueryId', ?list('SqlToken'), ?'Tail'). 1559:-chr_constraint write_group_bys(-'QueryId'). 1560:-chr_constraint write_in_list(-'QueryId', +'Disposition', +'Schema', +'TableName', +'AttributeName', +list('ApplicationValue')). 1561:-chr_constraint write_insert_attribute_name(-'QueryId', +'AttributeName'). 1562:-chr_constraint write_insert_attribute_names(-'QueryId', +list('AttributeNameValuePair')). 1563:-chr_constraint write_insert_value(-'QueryId', +'Schema', +'TableName', +'AttributeName', ?'ApplicationValue'). 1564:-chr_constraint write_insert_values(-'QueryId', +'Schema', +'TableName', ?list('AttributeNameValuePair')). 1565:-chr_constraint write_join(-'QueryId', -'Join'). 1566:-chr_constraint write_join_ons(-'QueryId', ?'On'). 1567:-chr_constraint write_limit. 1568:-chr_constraint write_lock_hint(-'QueryId', +'Schema', ?'TableAlias'). 1569:-chr_constraint write_order_by(-'QueryId', ?'OrderBy'). 1570:-chr_constraint write_order_by_attribute(-'QueryId', ?list('SqlToken'), ?'Tail'). 1571:-chr_constraint write_order_bys(-'QueryId', ?list('OrderBy')). 1572:-chr_constraint write_query_sql. 1573:-chr_constraint write_restriction(-'QueryId', ?'CompilationInstruction', +'Disposition', ?'ApplicationValue', +'ComparisonOperator', ?'ApplicationValue'). 1574:-chr_constraint write_restriction_1(-'QueryId', ?'CompilationInstruction', +'Disposition', +'OdbcDataType', ?'OdbcDataType', +'Schema', +'TableName', +'AttributeName', ?'RestrictionExpression', +'ComparisonOperator', ?'RestrictionExpression'). 1575:-chr_constraint write_restriction_expression(-'QueryId', ?'CompilationInstruction', +'Disposition', ?'OdbcDataType', +'OdbcDataType', +'Schema', +'TableName', +'AttributeName', ?'RestrictionExpression'). 1576:-chr_constraint write_restriction_tree(-'QueryId', +'Disposition', ?'RestrictionTree'). 1577:-chr_constraint write_select_attribute(-'QueryId', ?'CompilationInstruction', ?list('SqlToken'), ?'Tail', ?'Output'). 1578:-chr_constraint write_select_attribute_1(-'QueryId', ?'CompilationInstruction', ?list('SqlToken'), ?'Tail', ?'Output'). 1579:-chr_constraint write_select_attributes(-'QueryId'). 1580:-chr_constraint write_sql(-'QueryId', ?'CompilationInstruction',  +'Disposition', +list('SqlToken'), ?'Tail', ?list('OdbcParameter'), ?list('Output')). 1581:-chr_constraint write_update_attribute(-'QueryId', ?'TableAlias', +'AttributeName', ?'ApplicationValue'). 1582:-chr_constraint write_update_attributes(-'QueryId', ?'TableAlias', ?list('AttributeNameValuePair')). 1583
 1584
 1585:-op(400, xfy, (::)).            % CQL
 1586:-op(900, fy,  exists).          % CQL
 1587:-op(750, yfx, *==).             % CQL
 1588:-op(750, yfx, =*=).             % CQL
 1589:-op(750, yfx, ==*).             % CQL
 1590:-op(740, yfx, on).              % CQL
 1591:-op(700, xfx, =~).              % CQL (LIKE)
 1592:-op(700, xfx, \=~).             % CQL (NOT LIKE)
 1593:-op(200, fy, #).                % CQL (nolock)
 1594:-op(920, fy, ???).              % Debugging
 1595:-op(920, fy, ??).               % Debugging
 1596:-op(920, fy, ?).                % Debugging
 cql_set_module_default_schema(+Schema)
Set the Schema for a module
 1604:-dynamic
 1605        module_default_schema/2. 1606
 1607cql_set_module_default_schema(Schema) :-                       % +
 1608        prolog_load_context(module, Module),
 1609        set_module_default_schema(Module, Schema).
 1610
 1611
 1612
 1613set_module_default_schema(Module,      % +
 1614                          Schema) :-   % +
 1615        retractall(module_default_schema(Module, _)),
 1616        assert(module_default_schema(Module, Schema)).
 cql_get_module_default_schema(+Module, ?ModuleDefaultSchema)
 1621cql_get_module_default_schema(Module,                          % +
 1622                              ModuleDefaultSchema) :-          % ?
 1623
 1624        ( module_default_schema(Module, Schema) ->
 1625            ModuleDefaultSchema = Schema
 1626        ;
 1627            default_schema(ModuleDefaultSchema)
 1628        ).
 1629
 1630% This lets me control the compiletime checks via an environment variable
 1631:-dynamic(do_cql_compiletime_checks/1). 1632do_cql_compiletime_checks:-
 1633        ( do_cql_compiletime_checks(Status)->
 1634            Status == true
 1635        ; getenv('CQL_COMPILETIME_CHECKS', Atom)->
 1636            assert(do_cql_compiletime_checks(Atom)),
 1637            Atom == true
 1638        ; otherwise->
 1639            assert(do_cql_compiletime_checks(false)),
 1640            fail
 1641        ).
 1642
 1643cql_compiletime_checks(Schema, Goals):-
 1644        forall(cql_sql_clause(Goals, SQL, Parameters),
 1645               check_decompilation(Schema, SQL, Parameters)).
 1646
 1647check_decompilation(Schema, HalfCompiledSql, HalfCompiledOdbcParameters):-
 1648        dbms(Schema, DBMS),
 1649        ( fully_compile_sql(HalfCompiledSql, HalfCompiledOdbcParameters, [], Sql, OdbcParameters, _),
 1650          atom_codes(Sql, SqlCodes),
 1651          sql_tokens(Tokens, SqlCodes, []),
 1652          findall(test,
 1653                    ( member(odbc_parameter(_, _, _, _, _, _), OdbcParameters)
 1654                    ; member(odbc_explicit_type_parameter(_, _, _), OdbcParameters)
 1655                    ),
 1656                  Bindings),
 1657          sql_parse(action(Expression, _Types), _, [dbms(DBMS)], Tokens),
 1658          with_output_to(atom(Atom), sql_write(current_output, Expression, [dbms(DBMS), parameter_bindings(Bindings), suppress_collations]))->
 1659            % Make sure that the COLLATEs are all removed
 1660            \+sub_atom(Atom, _, _, _, 'COLLATE')
 1661        ; otherwise->
 1662            prolog_load_context(source, FileName),
 1663            prolog_load_context(term_position, TermPosition),
 1664            stream_position_data(line_count, TermPosition, LineNumber),
 1665            format(user_error, 'Could not decompile generated CQL: ~w~n~q~n', [FileName:LineNumber, HalfCompiledSql])
 1666        ).
 cql_goal_expansion(?Schema, ?Cql, ?GoalExpansion)
Expand at compile time if the first term is a list of unbound input variables

Expand at runtime if the first term is compile_at_runtime

 1680cql_goal_expansion(Schema, Cql, GoalExpansion) :-
 1681        % {} is also used by clp(r,q) so make sure the CQL looks like CQL
 1682        nonvar(Cql),
 1683        Cql = (Arg, _),
 1684        ( is_list(Arg)
 1685        ; nonvar(Arg),
 1686          Arg = compile_at_runtime(_)
 1687        ),
 1688
 1689        \+current_prolog_flag(xref, true), % Prevent expansion when used by pldoc to prevent spurious CQL compile errors
 1690        atom(Schema),
 1691        ( cql_goal_expansion_1(Schema, Cql, GoalExpansion_) ->
 1692            GoalExpansion = GoalExpansion_
 1693        ;
 1694            throw(format('Cannot expand CQL: Schema = ~w, Cql=(~w)', [Schema, Cql]))
 1695        ),
 1696        ( do_cql_compiletime_checks ->
 1697            setup_call_cleanup(assert(skip_cql_instantiation_check),
 1698                               cql_compiletime_checks(Schema, GoalExpansion),
 1699                               retract(skip_cql_instantiation_check))
 1700        ; otherwise->
 1701            true
 1702        ).
 1703
 1704
 1705cql_sql_clause(cql_odbc_state_change_statement(_, _, _, _, SQL, Parameters, _), SQL, Parameters).
 1706cql_sql_clause(cql_pre_state_change_select_sql(_, _, _, _, SQL, _, Parameters), SQL, Parameters).
 1707cql_sql_clause(cql_post_state_change_select_sql(_, _, Parameter, SQL), SQL, [odbc_explicit_type_parameter(Parameter, _, where_value)]).
 1708cql_sql_clause(cql_odbc_select_statement(_, SQL, Parameters, _), SQL, Parameters).
 1709cql_sql_clause((A, B), SQL, Parameters):-
 1710        ( cql_sql_clause(A, SQL, Parameters)
 1711        ; cql_sql_clause(B, SQL, Parameters)
 1712        ).
 1713
 1714:-multifile(cql_dependency_hook/2). 1715:-multifile(cql_generated_sql_hook/3). 1716cql_goal_expansion_1(Schema, (CompilationDirective, CqlA), GoalExpansion) :-
 1717        ( prolog_load_context(source, FileName),
 1718          prolog_load_context(term_position, TermPosition),
 1719          stream_position_data(line_count, TermPosition, LineNumber)->
 1720            DynamicallyCreatedCql = boolean(false)
 1721
 1722        ; otherwise ->
 1723            DynamicallyCreatedCql = boolean(true),
 1724            FileName = '<Dynamically created CQL - no source file>',
 1725            LineNumber = 0
 1726        ),
 1727
 1728        ( is_list(CompilationDirective),
 1729          EqualityRestrictionVariables = CompilationDirective,
 1730          forall(member(EqualityRestrictionVariable, EqualityRestrictionVariables), var(EqualityRestrictionVariable)) ->
 1731            CqlB = (store_equality_restriction_variables(EqualityRestrictionVariables),
 1732                    original_cql(CqlA),
 1733                    cql_statement_location(FileName, LineNumber),
 1734                    CqlA),
 1735            translate_to_constraints(Schema, CqlB, InitialConstraints),
 1736            call(InitialConstraints),
 1737            compile_mode(compiletime),
 1738            fully_compile,
 1739            runtime_constraints(cql_execute(cache_odbc_statement)),
 1740            collect_runtime_constraints(GoalExpansion),
 1741            referenced_tables(ReferencedTables),
 1742            ( ReferencedTables \== [],
 1743              DynamicallyCreatedCql == boolean(false) ->
 1744                sort(ReferencedTables, ReferencedTableSet),  % Remove duplicates
 1745                file_base_name(FileName, FileBaseName),
 1746                file_name_extension(Module, _, FileBaseName),
 1747                ignore(cql_dependency_hook(ReferencedTableSet, Module))
 1748
 1749            ; otherwise ->
 1750                true
 1751            ),
 1752            ignore(cql_generated_sql_hook(FileName, LineNumber, GoalExpansion))
 1753        ; nonvar(CompilationDirective),
 1754          CompilationDirective = compile_at_runtime(IgnoreIfNullVariables) ->
 1755            % Should this be a compile warning? runtime-compilation should now be officially deprecated
 1756            ( nonvar(IgnoreIfNullVariables) ->
 1757                variable_map(IgnoreIfNullVariables, CqlA, CqlB, VariableMap)
 1758
 1759            ; otherwise ->
 1760                true
 1761            ),
 1762            GoalExpansion = cql_runtime(Schema, IgnoreIfNullVariables, CqlA, CqlB, VariableMap, FileName, LineNumber)
 1763        ; otherwise ->
 1764            throw(error(domain_error(cql_compilation_directive, CompilationDirective), _))
 1765        ).
 cql_runtime(+Schema, +IgnoreIfNullVariables, +CqlA, +CqlB, +VariableMap, +FileName, +LineNumber)
 1771cql_runtime(Schema, IgnoreIfNullVariables, CqlA, CqlB, VariableMap, FileName, LineNumber) :-
 1772        catch(cql_runtime_1(Schema, IgnoreIfNullVariables, CqlA, CqlB, VariableMap, FileName, LineNumber),
 1773              format(Format, Arguments),  % Want a backtrace for compile errors in compile_at_runtime statements at runtime
 1774              cql_error(cql, Format, Arguments)).
 1775
 1776
 1777cql_runtime_1(Schema, IgnoreIfNullVariables, CqlA, CqlB, VariableMap, FileName, LineNumber) :-
 1778        ( var(VariableMap) ->
 1779            % Handle the case where IgnoreIfNullVariables is dynamically generated
 1780            variable_map(IgnoreIfNullVariables, CqlA, CqlB, VariableMap)
 1781
 1782        ; otherwise ->
 1783            true
 1784        ),
 1785        CqlC = (store_ignore_if_null_variables(VariableMap),
 1786                original_cql(CqlA),
 1787                cql_statement_location(FileName, LineNumber),
 1788                CqlB),
 1789        translate_to_constraints(Schema, CqlC, InitialConstraints),
 1790        call(InitialConstraints),
 1791        fully_compile,
 1792        cql_execute(do_not_cache_odbc_statement),
 1793        referenced_tables(_).    % Clean up
 1794
 1795
 1796variable_map(IgnoreIfNullVariables, CqlA, CqlB, VariableMap) :-
 1797        copy_term(CqlA, CqlB),
 1798        term_variables(CqlA, ExternalVariables),
 1799        term_variables(CqlB, InternalVariables),
 1800        variable_map_1(ExternalVariables, InternalVariables, IgnoreIfNullVariables, VariableMap).
 1801
 1802
 1803
 1804variable_map_1([], [], _, []).
 1805
 1806variable_map_1([A|As], [B|Bs], IgnoreIfNullVariables, [A-B|VariableMap]) :-
 1807        select(I, IgnoreIfNullVariables, Rest),
 1808        I == A, !,
 1809        variable_map_1(As, Bs, Rest, VariableMap).
 1810
 1811variable_map_1([V|As], [V|Bs], IgnoreIfNullVariables, VariableMap) :-
 1812        variable_map_1(As, Bs, IgnoreIfNullVariables, VariableMap).
 1813
 1814
 1815
 1816translate_to_constraints(Schema,                      % +
 1817                         Cql,                         % +
 1818                         InitialConstraints) :-       % ?
 1819        create_variable_dictionary(Cql, [], CqlGround, Dictionary),
 1820        findall(QueryId-Conjunction,
 1821                translate_to_constraints_1(Schema, top_level_query, CqlGround, QueryId, Conjunction),
 1822                Conjunctions),
 1823        store_conjunctions(Conjunctions, Dictionary),
 1824        conjunction_constraints(true),
 1825        get_conjunction_constraints(InitialConstraints).
 1826
 1827
 1828
 1829store_conjunctions([], _).
 1830
 1831store_conjunctions([QueryId-Conjunction|Conjunctions], Dictionary) :-
 1832        store_conjunction(Conjunction, QueryId, Dictionary),
 1833        store_conjunctions(Conjunctions, Dictionary).
 1834
 1835
 1836
 1837store_conjunction([], _, _).
 1838
 1839store_conjunction([Goal|Goals], QueryId, Dictionary) :-
 1840        create_conjunction_variables(Goal, QueryId, Dictionary, ConjunctionGoal),
 1841        conjunction_goal(ConjunctionGoal),
 1842        store_conjunction(Goals, QueryId, Dictionary).
 1843
 1844
 1845collect_conjunction_variables @
 1846        conjunction_constraints(Constraints),
 1847        conjunction_variable(QueryId, ExternalVariable, ConjunctionVariable)
 1848        <=>
 1849        conjunction_constraints((conjunction_variable(QueryId, ExternalVariable, ConjunctionVariable), Constraints)).
 1850
 1851
 1852collect_conjunction_goals @
 1853        conjunction_constraints(Constraints),
 1854        conjunction_goal(ConjunctionGoal)
 1855        <=>
 1856        conjunction_constraints((ConjunctionGoal, Constraints)).
 1857
 1858
 1859get_conjunction_constraints @
 1860        get_conjunction_constraints(Constraints),
 1861        conjunction_constraints(C)
 1862        <=>
 1863        C = Constraints.
 1864
 1865
 1866
 1867create_variable_dictionary(Term,                     % +
 1868                           Dictionary,               % +
 1869                           GroundTerm,               % ?
 1870                           NewDictionary) :-         % ?
 1871        ( ground(Term) ->
 1872            GroundTerm = Term,
 1873            NewDictionary = Dictionary
 1874
 1875        ; var(Term) ->
 1876            ( member(Variable-GroundTerm, Dictionary),
 1877              Variable == Term ->
 1878                NewDictionary = Dictionary
 1879            ; var_property(Term, fresh(false))->
 1880                gensym(cql_stale_var_, UniqueAtom),
 1881                GroundTerm = '$VAR'(UniqueAtom),
 1882                NewDictionary = [Term-GroundTerm|Dictionary]
 1883            ; otherwise->
 1884                gensym(cql_var_, UniqueAtom),
 1885                GroundTerm = '$VAR'(UniqueAtom),
 1886                NewDictionary = [Term-GroundTerm|Dictionary]
 1887            )
 1888
 1889        ; otherwise ->
 1890            functor(Term, Name, Arity),
 1891            functor(GroundTerm, Name, Arity),
 1892            add_args_to_dictionary(Term, Dictionary, 1, Arity, GroundTerm, NewDictionary)
 1893        ).
 1894
 1895
 1896
 1897add_args_to_dictionary(Term, Dictionary, N, Arity, GroundTerm, NewDictionary) :-
 1898        ( N > Arity ->
 1899            NewDictionary = Dictionary
 1900        ;
 1901            arg(N, Term, Arg),
 1902            create_variable_dictionary(Arg, Dictionary, GroundArg, DictionaryA),
 1903            arg(N, GroundTerm, GroundArg),
 1904            NextN is N + 1,
 1905            add_args_to_dictionary(Term, DictionaryA, NextN, Arity, GroundTerm, NewDictionary)
 1906        ).
 1907
 1908
 1909dictionary_lookup @
 1910        % This allows us to define new join points and tables as we compile (eep?)
 1911        dictionary_addendum(QueryId, A, C)
 1912        \
 1913        dictionary_lookup(QueryId, A, B)
 1914        <=>
 1915        B = C.
 1916
 1917failed_to_get_dictionary_addendum @
 1918        dictionary_lookup(_,_,_)
 1919        <=>
 1920        fail.
 1921
 1922cql_stale:attr_unify_hook(_,_).
 1923create_conjunction_variables(Term, QueryId, Dictionary, TermWithVariables) :-
 1924        ( var(Term) ->
 1925            TermWithVariables = Term
 1926        ; memberchk(ExternalVariable-Term, Dictionary) ->
 1927            conjunction_variable(QueryId, ExternalVariable, ConjunctionVariable),
 1928            ( Term = '$VAR'(Key),
 1929              atom_prefix(Key, cql_stale_var_)->
 1930                put_attr(ConjunctionVariable, cql_stale, 1)
 1931            ; otherwise->
 1932                true
 1933            ),
 1934            TermWithVariables = ConjunctionVariable
 1935        ; dictionary_lookup(QueryId, Term, Var)->
 1936            TermWithVariables = Var
 1937        ; atomic(Term) ->
 1938           TermWithVariables = Term
 1939
 1940        ; otherwise ->
 1941           functor(Term, Name, Arity),
 1942           functor(TermWithVariables, Name, Arity),
 1943           add_arg_variables(Term, QueryId, Dictionary, 1, Arity, TermWithVariables)
 1944        ).
 1945
 1946
 1947
 1948add_arg_variables(Term, QueryId, Dictionary, N, Arity, TermWithVariables) :-
 1949        ( N > Arity ->
 1950            true
 1951        ;
 1952            arg(N, Term, Arg),
 1953            create_conjunction_variables(Arg, QueryId, Dictionary, NewArg),
 1954            arg(N, TermWithVariables, NewArg),
 1955            NextN is N + 1,
 1956            add_arg_variables(Term, QueryId, Dictionary, NextN, Arity, TermWithVariables)
 1957        ).
 1958
 1959
 1960
 1961share_conjunction_variable @
 1962        conjunction_variable(QueryId, ExternalVariable, ConjunctionVariableA)
 1963        \
 1964        conjunction_variable(QueryId, ExternalVariable, ConjunctionVariableB)
 1965        <=>
 1966        ConjunctionVariableA = ConjunctionVariableB.
 1967
 1968
 1969bind_conjunction_variable_if_external_variable_gets_bound @
 1970        conjunction_variable(_, ExternalVariable, ConjunctionVariable)
 1971        <=>
 1972        nonvar(ExternalVariable)
 1973        |
 1974        ConjunctionVariable = ExternalVariable.
 1975
 1976
 1977bind_external_variables_once_fully_compiled @
 1978        cql_fully_compiled
 1979        \
 1980        conjunction_variable(_, ExternalVariable, ConjunctionVariable)
 1981        <=>
 1982        ExternalVariable = ConjunctionVariable.
 1983
 1984
 1985
 1986translate_to_constraints_1(Schema, QueryLevel, Cql, QueryId, CqlConstraints) :-
 1987        ( translate_to_constraints_2(Schema, QueryLevel, Cql, QueryId, CqlConstraints, []) *->
 1988
 1989            ( msort(CqlConstraints, SortedCqlConstraints),
 1990              nextto(state_change_query(_, _, _, _), state_change_query(_, _, _, _), SortedCqlConstraints) ->
 1991                throw(format('Cannot mix state change queries in a single CQL statement', []))
 1992            ;
 1993                true
 1994            )
 1995        ;
 1996           throw(format('Cannot translate CQL: ~w~n', [Cql]))
 1997        ).
 1998
 1999
 2000%       translate_to_constraints_2//4
 2001%
 2002%       QueryId is a variable identifying a query (or sub-query).  The
 2003%       top of the JOIN and WHERE trees is the QueryId
 2004
 2005translate_to_constraints_2(Schema, QueryLevel, Cql, QueryId) -->
 2006        translate(Schema, QueryId, QueryId, Cql),
 2007        [query(QueryId, Schema, QueryLevel),
 2008         restriction_tree(QueryId, where, true),
 2009         sql_statement(QueryId, A, A, B, B, C, C, [], [], [])].
 2010
 2011
 2012%       translate//4
 2013
 2014translate(_, _, _, compile_time_goal(Goal)) --> !,
 2015        {(Goal = Module:Goal1 ->
 2016             true
 2017         ; otherwise->
 2018             prolog_load_context(module, Module),
 2019             Goal1 = Goal
 2020         )},
 2021        [Module:Goal1].
 2022
 2023translate(_, _, _, original_cql(Cql)) --> !,
 2024        [original_cql(Cql)].
 2025
 2026translate(_, _, _, cql_statement_location(FileName, LineNumber)) --> !,
 2027        [cql_statement_location(FileName, LineNumber)].
 2028
 2029translate(_, _, _, store_equality_restriction_variables(EqualityRestrictionVariables)) --> !,
 2030        [store_equality_restriction_variables(EqualityRestrictionVariables)].
 2031
 2032translate(_, _, _, store_ignore_if_null_variables(VariableMap)) --> !,
 2033        [store_ignore_if_null_variables(VariableMap)].
 2034
 2035translate(_, _, _, Term) -->
 2036        {functor(Term, \+, Arity),
 2037         Arity \== 1,
 2038        throw(format('Negation (\\+) is arity one ... add some parentheses: ~w', [Term]))}.
 2039
 2040translate(Schema, QueryId, ParentJoin, (Lhs ; Rhs)) --> !,     % BTP (compile time!)
 2041        (translate(Schema, QueryId, ParentJoin, Lhs)
 2042        ;
 2043        translate(Schema, QueryId, ParentJoin, Rhs)).
 2044
 2045translate(Schema, QueryId, ParentJoin, (Lhs, Rhs)) --> !,
 2046        translate(Schema, QueryId, ParentJoin, Lhs),
 2047        translate(Schema, QueryId, ParentJoin, Rhs).
 2048
 2049
 2050% if we update FROM in postgres, we get an automatic join to the table we're updating
 2051% We need to push things from the @ :: [...] into the where clause, and not have them in the join
 2052% in fact, we shouldn't even list the table in the join unless we're doing a self-join
 2053% (or I guess an outer join).
 2054
 2055% I think that a right outer join in an update is the same as in inner join for all intents and purposes
 2056translate(Schema, QueryId, ParentJoin, JoinTerm) -->
 2057        {dbms(Schema, 'PostgreSQL')},
 2058        { JoinTerm =.. [JoinOperator, Lhs, on(Rhs, On)],
 2059          (join(JoinOperator, 'INNER JOIN') ; join(JoinOperator, 'RIGHT OUTER JOIN'))
 2060        },
 2061        {Lhs = (@ :: _) ; Rhs = (@ :: _)},
 2062        !,
 2063        translate(Schema, QueryId, ParentJoin, Lhs),
 2064        translate(Schema, QueryId, ParentJoin, Rhs),
 2065        translate(Schema, QueryId, ParentJoin, On),
 2066        [implicit_join(QueryId, @, SubQueryId),
 2067         implicit_join_link(QueryId, SubQueryId),
 2068         on(SubQueryId, _, On)].
 2069
 2070translate(Schema, QueryId, ParentJoin, JoinTerm) -->
 2071        {dbms(Schema, 'PostgreSQL')},
 2072        { JoinTerm =.. [JoinOperator, Lhs, Rhs],
 2073          (join(JoinOperator, 'INNER JOIN') ; join(JoinOperator, 'RIGHT OUTER JOIN'))
 2074        },
 2075        {Lhs = (@ :: _) ; Rhs = (@ :: _)},
 2076        !,
 2077        translate(Schema, QueryId, ParentJoin, Lhs),
 2078        translate(Schema, QueryId, ParentJoin, Rhs),
 2079        [implicit_join(QueryId, @, _)].
 2080
 2081
 2082% This gets very very unpleasant. To do a left outer join in the update, we have to first do an inner join the target
 2083% and then outer join from THERE to complete. Postgres does NOT support left outer join in the from clause otherwise.
 2084% note that FROM in an update is not standard SQL anyway.
 2085translate(Schema, QueryId, ParentJoin, JoinTerm) -->
 2086        {dbms(Schema, 'PostgreSQL')},
 2087        { JoinTerm =.. [JoinOperator, Lhs, Rhs],
 2088          join(JoinOperator, 'LEFT OUTER JOIN')
 2089        },
 2090        {Lhs = (@ :: Conditions)}, % don't allow for the target to be on the right. That doesn't really make a lot of sense anyway
 2091        !,
 2092        % Effectively we translate
 2093        %    @ :: [a-A, ...] ==* z :: [z-A, ...]
 2094        % into
 2095        %    (@ :: [a-A, ..., pk-Pk] =*= @@ :: [pk-Pk]) ==* z :: [z-A, ...]
 2096        % Where @@ is a symbol to mean 'the same table as the target but a different alias'
 2097        % The first part of this is dropped as an implicit join
 2098
 2099        % First off, we need to save space for the key. If we don't add this cql_var_X to the
 2100        % dictionary somehow, it will be translated as if cql_var_X were a literal for the WHERE clause
 2101         {gensym(cql_var_, KeyInfo),
 2102          dictionary_addendum(QueryId, KeyInfo, Variable),
 2103          append(Conditions, KeyInfo, NewConditions)},
 2104         [update_table_key(QueryId, Schema, Variable)],
 2105         translate(Schema, QueryId, ParentJoin, (@ :: KeyInfo =*= ((@@) :: NewConditions)) *== Rhs).
 2106
 2107
 2108translate(Schema, QueryId, ParentJoin, JoinTerm) -->
 2109        { JoinTerm =.. [JoinOperator, Lhs, on(Rhs, On)],
 2110          join(JoinOperator, JoinType)
 2111        }, !,
 2112        translate(Schema, QueryId, LhsJoin, Lhs),
 2113        translate(Schema, QueryId, RhsJoin, Rhs),
 2114
 2115        [on(ParentJoin, _, On),
 2116         join(QueryId, ParentJoin, LhsJoin, JoinType, RhsJoin)].
 2117
 2118translate(Schema, QueryId, ParentJoin, JoinTerm) -->
 2119        { JoinTerm =.. [JoinOperator, Lhs, Rhs],
 2120          join(JoinOperator, JoinType)
 2121        },
 2122        !,
 2123        translate(Schema, QueryId, LhsJoin, Lhs),
 2124        translate(Schema, QueryId, RhsJoin, Rhs),
 2125
 2126        [join(QueryId, ParentJoin, LhsJoin, JoinType, RhsJoin)].
 2127
 2128
 2129
 2130translate(Schema,
 2131          QueryId,
 2132          ParentJoin,
 2133          @ :: AttributeNameValuePairs) --> !,   % '@' means the update table
 2134        [store_attribute_bindings(Schema, QueryId, TableAlias, AttributeNameValuePairs),
 2135         attributes_to_check(QueryId, Schema, @, AttributeNameValuePairs),
 2136         update_table_alias(QueryId, Schema, ParentJoin, TableAlias)].
 2137
 2138translate(Schema,
 2139          QueryId,
 2140          ParentJoin,
 2141          (@@) :: AttributeNameValuePairs) --> !,   % '@@' means a copy of update table
 2142        [store_attribute_bindings(Schema, QueryId, TableAlias, AttributeNameValuePairs),
 2143         attributes_to_check(QueryId, Schema, @, AttributeNameValuePairs),
 2144         query_table_alias(QueryId, Schema, (@@), TableAlias),
 2145         join_leaf(ParentJoin, TableAlias)].
 2146
 2147translate(Schema,
 2148          QueryId,
 2149          ParentJoin,
 2150          #TableName :: AttributeNameValuePairs) --> !,   % '#' means nolock
 2151        translate_select(Schema,
 2152                         QueryId,
 2153                         ParentJoin,
 2154                         TableName,
 2155                         AttributeNameValuePairs, QueryTableAlias),
 2156        [nolock(QueryId, QueryTableAlias)].
 2157
 2158translate(Schema,
 2159          QueryId,
 2160          ParentJoin,
 2161          TableName :: AttributeNameValuePairs) --> !,
 2162        translate_select(Schema,
 2163                         QueryId,
 2164                         ParentJoin,
 2165                         TableName,
 2166                         AttributeNameValuePairs,
 2167                         _).
 2168
 2169translate(Schema, QueryId, _, insert(TableName, AttributeNameValuePairs)) --> !,
 2170        {\+ duplicate_attributes(insert, Schema, TableName, AttributeNameValuePairs)},
 2171        [insert(QueryId, Schema, TableName, AttributeNameValuePairs),
 2172         query_type(QueryId, insert),
 2173         attributes_to_check(QueryId, Schema, TableName, AttributeNameValuePairs),
 2174         state_change_query(QueryId, insert, Schema, TableName)].
 2175
 2176translate(Schema, QueryId, _, update(TableName, UpdateAttributeNameValuePairs)) --> !,
 2177        {\+ duplicate_attributes(update, Schema, TableName, UpdateAttributeNameValuePairs)},
 2178        [update(QueryId, Schema, TableName, _, UpdateAttributeNameValuePairs),
 2179         query_type(QueryId, update),
 2180         attributes_to_check(QueryId, Schema, TableName, UpdateAttributeNameValuePairs),
 2181         state_change_query(QueryId, update, Schema, TableName)].
 2182
 2183translate(Schema, QueryId, ParentJoin, delete(TableName, AttributeNameValuePairs)) --> !,
 2184        {\+ duplicate_attributes(delete, Schema, TableName, AttributeNameValuePairs)},
 2185        [delete_row(QueryId, TableName, TableAlias),
 2186         query_type(QueryId, delete),
 2187         attributes_to_check(QueryId, Schema, TableName, AttributeNameValuePairs),
 2188         store_attribute_bindings(Schema, QueryId, TableAlias, AttributeNameValuePairs),
 2189         join_leaf(ParentJoin, TableAlias),
 2190         query_table_alias(QueryId, Schema, TableName, TableAlias),
 2191         state_change_query(QueryId, delete, Schema, TableName)].
 2192
 2193translate(Schema, QueryId, ParentJoin, \+((Lhs, Rhs))) --> !,     % De Morgan
 2194        translate(Schema, QueryId, ParentJoin, (\+Lhs ; \+Rhs)).
 2195
 2196translate(Schema, QueryId, ParentJoin, \+((Lhs ; Rhs))) --> !,    % De Morgan
 2197        translate(Schema, QueryId, ParentJoin, (\+Lhs, \+Rhs)).
 2198
 2199translate(Schema, QueryId, _, \+Comparison) -->
 2200        {simple_comparison(Schema, Comparison, _, InverseOperator, Lhs, Rhs)}, !,
 2201        translate_comparison(QueryId, Schema, Lhs, InverseOperator, Rhs).
 2202
 2203translate(Schema, QueryId, _, Comparison) -->
 2204        {simple_comparison(Schema, Comparison, Operator, _, Lhs, Rhs)}, !,
 2205        translate_comparison(QueryId, Schema, Lhs, Operator, Rhs).
 2206
 2207translate(Schema, QueryId, _, \+ exists(Goals)) --> !,
 2208        translate_sub_query(Schema, QueryId, \+ exists, Goals).
 2209
 2210translate(Schema, QueryId, _, exists(Goals)) --> !,
 2211        translate_sub_query(Schema, QueryId, exists, Goals).
 2212
 2213translate(_, QueryId, _, group_by(GroupBys)) --> !,
 2214        [group_bys(QueryId, GroupBys)].
 2215
 2216translate(_, QueryId, _, order_by(OrderBys)) --> !,
 2217        [order_bys(QueryId, OrderBys)].
 2218
 2219translate(Schema, QueryId, _, having(Having)) --> !,
 2220        {prolog_term_to_restriction_tree(Schema, Having, RestrictionTree)},
 2221        [restriction_tree(QueryId, having, RestrictionTree)].
 2222
 2223translate(_, QueryId, _, distinct) --> !,
 2224        [select_distinction(QueryId, distinct_on_all_select_attributes)].
 2225
 2226translate(_, QueryId, _, distinct(Distincts)) --> !,
 2227        [distincts(QueryId, Distincts)].
 2228
 2229translate(Schema, QueryId, _, top(N)) --> !,
 2230        [top(QueryId, Schema, N)].
 2231
 2232translate(Schema, QueryId, _, identity(I)) --> !,
 2233        [cql_identity(QueryId, Schema, I)].
 2234
 2235translate(_, QueryId, _, row_count(N)) --> !,
 2236        [row_count(QueryId, N)].
 2237
 2238translate(_, _, _, absence_of_where_restriction_is_deliberate) --> !,
 2239        [absence_of_where_restriction_is_deliberate].
 2240
 2241translate(_, _, _, A=B) --> !,
 2242        {(prolog_load_context(source, FileName),
 2243          prolog_load_context(term_position, TermPosition),
 2244          stream_position_data(line_count, TermPosition, LineNumber)->
 2245            true
 2246         ; otherwise->
 2247            FileName = '<Dynamically created CQL - no source file>',
 2248            LineNumber = 0
 2249         ),
 2250        print_message(warning, format('Unification in CQL is DEPRECATED (~w:~w)~n', [FileName, LineNumber]))},
 2251        [unify(A, B)].
 2252
 2253translate(_, _, _, true) --> !,
 2254        [].
 2255
 2256translate(_, QueryId, _, no_state_change_actions) --> !,
 2257        [no_state_change_actions(QueryId)].
 2258
 2259translate(_, _, _, Term) -->
 2260        {throw(format('Cannot translate CQL term: ~w~n', [Term]))}.
 2261
 2262
 2263join(*==, 'LEFT OUTER JOIN').
 2264join(=*=, 'INNER JOIN').
 2265join(==*, 'RIGHT OUTER JOIN').
 2266
 2267
 2268translate_sub_query(Schema, QueryId, SubQueryType, Goals) -->
 2269        translate_to_constraints_2(Schema, sub_query, Goals, SubQueryId), !,
 2270        [sub_query_select(SubQueryId),
 2271         sub_query_restriction(QueryId, SubQueryType, SubQuerySqlTokens, SubQueryTail, SubQueryInputs),
 2272         sub_query(SubQueryId, SubQuerySqlTokens, SubQueryTail, SubQueryInputs)].
 2273
 2274
 2275translate_select(Schema,                     % +
 2276                 QueryId,                    % +
 2277                 ParentJoin,                 % +
 2278                 TableName,                  % +
 2279                 AttributeNameValuePairs,    % +
 2280                 QueryTableAlias) -->        % ?
 2281        [store_attribute_bindings(Schema, QueryId, QueryTableAlias, AttributeNameValuePairs),
 2282         query_type(QueryId, select),
 2283         attributes_to_check(QueryId, Schema, TableName, AttributeNameValuePairs),
 2284         join_leaf(ParentJoin, QueryTableAlias),
 2285         query_table_alias(QueryId, Schema, TableName, QueryTableAlias)].
 2286
 2287
 2288simple_comparison(Schema,                    % +
 2289                  Comparison,                % +
 2290                  Operator,                  % ?
 2291                  InverseOperator,           % ?
 2292                  Lhs,                       % ?
 2293                  Rhs) :-                    % ?
 2294        functor(Comparison, Operator, 2),
 2295        prolog_to_sql_comparison_operator(Schema, Operator, _, InverseOperator),
 2296        arg(1, Comparison, Lhs),
 2297        arg(2, Comparison, Rhs).
 2298
 2299
 2300translate_comparison(QueryId, Schema, Lhs, Operator, Rhs) -->
 2301        translate_expression(Schema, Lhs, LhsResult),
 2302        translate_expression(Schema, Rhs, RhsResult),
 2303
 2304        [comparison(QueryId, LhsResult, Operator, RhsResult)].
 2305
 2306
 2307translate_expression(Schema,
 2308                     Goal,
 2309                     aggregation_sub_query_sql(AggregationTableName, AggregationAttributeName, SubQuerySqlTokens, Tail, SubQueryInputs)) -->
 2310        {functor(Goal, AggregationOperator, 2),
 2311         aggregation_operator(AggregationOperator), !,
 2312         arg(1, Goal, AggregationVariable),
 2313         arg(2, Goal, Goals)},
 2314
 2315        translate_to_constraints_2(Schema, sub_query, Goals, SubQueryId),
 2316
 2317        [aggregation_variable(SubQueryId,
 2318                              AggregationOperator,
 2319                              AggregationVariable),
 2320         aggregation_sub_query(SubQueryId, AggregationTableName, AggregationAttributeName, SubQuerySqlTokens, Tail, SubQueryInputs)].
 2321
 2322
 2323translate_expression(_, Variable, Variable) -->
 2324        [true].
 2325
 2326
 2327aggregation_operator(count).
 2328aggregation_operator(max).
 2329aggregation_operator(min).
 2330aggregation_operator(avg).
 2331aggregation_operator(sum).
 2332
 2333
 2334prolog_term_to_restriction_tree(Schema, \+(Lhs, Rhs), RestrictionTree) :- !,
 2335        prolog_term_to_restriction_tree(Schema, (\+Lhs ; \+Rhs), RestrictionTree).
 2336
 2337prolog_term_to_restriction_tree(Schema, \+(Lhs ; Rhs), RestrictionTree) :- !,
 2338        prolog_term_to_restriction_tree(Schema, (\+Lhs, \+Rhs), RestrictionTree).
 2339
 2340prolog_term_to_restriction_tree(Schema, (Lhs, Rhs), and(RestrictionLhs, RestrictionRhs)) :- !,
 2341        prolog_term_to_restriction_tree(Schema, Lhs, RestrictionLhs),
 2342        prolog_term_to_restriction_tree(Schema, Rhs, RestrictionRhs).
 2343
 2344prolog_term_to_restriction_tree(Schema, (Lhs ; Rhs), or(RestrictionLhs, RestrictionRhs)) :- !,
 2345        prolog_term_to_restriction_tree(Schema, Lhs, RestrictionLhs),
 2346        prolog_term_to_restriction_tree(Schema, Rhs, RestrictionRhs).
 2347
 2348prolog_term_to_restriction_tree(Schema, \+Comparison, comparison(RestrictionLhs, InverseOperator, RestrictionRhs)) :- !,
 2349        simple_comparison(Schema, Comparison, _, InverseOperator, RestrictionLhs, RestrictionRhs).
 2350
 2351prolog_term_to_restriction_tree(Schema, Comparison, comparison(Lhs, Operator, Rhs)) :-
 2352        ( simple_comparison(Schema, Comparison, Operator, _, Lhs, Rhs) ->
 2353            true
 2354        ;
 2355            throw(format('Cannot translate restriction term: ~w', [Comparison]))
 2356        ).
 2357
 2358
 2359equality_restriction_variables_are_unique @
 2360        equality_restriction_variable(Variable, _)
 2361        \
 2362        equality_restriction_variable(Variable, _)
 2363        <=>
 2364        true.
 2365
 2366
 2367store_equality_restriction_variables @
 2368        store_equality_restriction_variables([InputVariable|InputVariables])
 2369        <=>
 2370        equality_restriction_variable(InputVariable, _),
 2371        store_equality_restriction_variables(InputVariables).
 2372
 2373
 2374cleanup_store_equality_restriction_variables @
 2375        store_equality_restriction_variables([])
 2376        <=>
 2377        true.
 2378
 2379
 2380store_ignore_if_null_variables @
 2381        store_ignore_if_null_variables([ExternalVariable-InternalVariable|VariableMap])
 2382        <=>
 2383        ignore_if_null(ExternalVariable, InternalVariable),
 2384        store_ignore_if_null_variables(VariableMap).
 2385
 2386
 2387cleanup_store_ignore_if_null_variables @
 2388        store_ignore_if_null_variables([])
 2389        <=>
 2390        true.
 2391
 2392
 2393store_attribute_bindings(Schema, QueryId, TableAlias, AttributeNameValuePairs) :-
 2394        ( store_attribute_bindings_1(Schema, QueryId, TableAlias, AttributeNameValuePairs) ->
 2395            true
 2396        ;
 2397            throw(format('Bad attribute bindings: ~w', [AttributeNameValuePairs]))
 2398        ).
 2399
 2400
 2401store_attribute_bindings_1(_, _, _, []).
 2402
 2403store_attribute_bindings_1(Schema, QueryId, TableAlias, [AttributeNameValuePair|AttributeNameValuePairs]) :-
 2404        % For INSERT from SELECTs
 2405        ( AttributeNameValuePair = as(AttributeName)-ApplicationValue ->
 2406            attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), selection_constant(ApplicationValue))
 2407
 2408        % Normal Name-Value specification
 2409        ; AttributeNameValuePair = AttributeName-ApplicationValue,
 2410          atomic_application_value(ApplicationValue) ->
 2411            attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), ApplicationValue)
 2412
 2413        % ignore_if_null
 2414        ; AttributeNameValuePair = (AttributeName-ignore_if_null(ApplicationValue)),
 2415          var(ApplicationValue)->
 2416            attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), AttributeValue),
 2417            comparison(QueryId, AttributeValue, ==, ignore_if_null(ApplicationValue))
 2418
 2419        % runtime list
 2420        ; AttributeNameValuePair = (AttributeName-list(ApplicationValue))->
 2421            attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), AttributeValue),
 2422            comparison(QueryId, AttributeValue, ==, list(ApplicationValue))
 2423
 2424        % Compile-time attribute value
 2425        ; AttributeNameValuePair = (AttributeName-CompileTimeGoal),
 2426          callable(CompileTimeGoal),
 2427          functor(CompileTimeGoal, PredicateName, ArityMinusOne),
 2428          Arity is ArityMinusOne + 1,
 2429          current_predicate(user:PredicateName/Arity),
 2430          user:call(CompileTimeGoal, ApplicationValue) ->
 2431            attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), ApplicationValue)
 2432        ),
 2433        store_attribute_bindings_1(Schema, QueryId, TableAlias, AttributeNameValuePairs).
 2434
 2435
 2436atomic_application_value(ApplicationValue) :-  % +
 2437        ( var(ApplicationValue)
 2438        ; atom(ApplicationValue)
 2439        ; integer(ApplicationValue)
 2440        ; rational(ApplicationValue)
 2441	; timestamp(ApplicationValue)
 2442        ; cql_atomic_value_check_hook(ApplicationValue)
 2443        ; is_list(ApplicationValue)
 2444        ; ApplicationValue == {null}
 2445        ; ApplicationValue == {timestamp}
 2446        ; ApplicationValue == {user_id}
 2447        ; ApplicationValue == {transaction_id}
 2448        ),
 2449        !.
 2450
 2451timestamp(TS) :-
 2452	compound(TS),
 2453	functor(TS, timestamp, 7).
 2454
 2455
 2456ensure_binding_is_on_the_external_variable_so_that_ignore_if_null_works_properly_1 @
 2457        ignore_if_null(ExternalVariable, InternalVariable)
 2458        \
 2459        unify(InternalVariable, X)
 2460        <=>
 2461        ExternalVariable = X.
 2462
 2463
 2464ensure_binding_is_on_the_external_variable_so_that_ignore_if_null_works_properly_2 @
 2465        ignore_if_null(ExternalVariable, InternalVariable)
 2466        \
 2467        unify(X, InternalVariable)
 2468        <=>
 2469        ExternalVariable = X.
 2470
 2471
 2472make_unify_unify @
 2473        unify(X, Y)
 2474        <=>
 2475        X = Y.
 2476
 2477
 2478remove_comparison_involving_ignored_variable @
 2479        ignore_if_null(ExternalVariable, InternalVariable)
 2480        \
 2481        comparison(_, Lhs, _, Rhs)
 2482        <=>
 2483        ( ExternalVariable == {null},
 2484          InternalVariable == Lhs
 2485
 2486        ; ExternalVariable == {null},
 2487          InternalVariable == Rhs
 2488
 2489        ; InternalVariable == Lhs,
 2490          Rhs == {null}
 2491
 2492        ; InternalVariable == Rhs,
 2493          Lhs == {null}
 2494        )
 2495        |
 2496        true.
 2497
 2498
 2499fully_compile @
 2500        fully_compile
 2501        <=>
 2502        no_sql_statement_generated,
 2503        unify_ignore_if_null_variables,
 2504        create_in_line_joins,
 2505        create_join_points,
 2506        resolve_join_points,
 2507        determine_select_distinctions,
 2508        create_select_bindings,
 2509        determine_selection_type,
 2510        create_restrictions,
 2511        generate_sub_query_sql,
 2512        simplify,
 2513        ( debugging(cql(compile)) ->
 2514            with_output_to(codes(Codes), chr_show_store(cql)),
 2515            debug(cql(compile), '==========~n~s^^^^^^^^^^~n~n', [Codes])
 2516        ;
 2517            true
 2518        ),
 2519        check_for_top_without_order_by,
 2520        write_query_sql,
 2521        instantiate_table_aliases,
 2522        write_limit,
 2523        check_for_orphan_select_attributes_in_aggregations,
 2524        check_query,
 2525        check_for_unjoined_tables,
 2526        check_for_orphan_group_bys,
 2527        check_for_orphan_order_bys,
 2528        check_for_orphan_distincts,
 2529        check_for_orphan_select_variables_in_updates,
 2530        prepare_odbc_statements,
 2531        cleanup_compile,
 2532        cql_fully_compiled.
 2533
 2534
 2535
 2536unify_ignore_if_null_variables @
 2537        unify_ignore_if_null_variables
 2538        \
 2539        ignore_if_null(ExternalVariable, InternalVariable)
 2540        <=>
 2541        nonvar(ExternalVariable),
 2542        ExternalVariable \== {null}
 2543        |
 2544        InternalVariable = ExternalVariable.
 2545
 2546
 2547cleanup_unify_ignore_if_null_variables @
 2548        unify_ignore_if_null_variables
 2549        <=>
 2550        true.
 2551
 2552
 2553update_atat_table_name @
 2554        update(QueryId, Schema, TableName, _, _)
 2555        \
 2556        query_table_alias(QueryId, Schema, (@@), Alias)
 2557        <=>
 2558        query_table_alias(QueryId, Schema, TableName, Alias).
 2559
 2560
 2561resolve_update_table_alias @
 2562        create_join_points,
 2563        update(QueryId, Schema, TableName, UpdateTableAlias, _),
 2564        update_table_alias(QueryId, _, ParentJoin, TableAlias)
 2565        ==>
 2566        join_leaf(ParentJoin, TableAlias),
 2567        query_table_alias(QueryId, Schema, TableName, TableAlias),
 2568        UpdateTableAlias = TableAlias.
 2569
 2570
 2571where_restriction_variable_not_allowed_to_be_an_outer_join_point @
 2572        outer_side_join(Join),
 2573        join_leaf(Join, TableAlias),
 2574        attribute_binding(_, attribute(_, TableAlias, _), JoinVariable),
 2575        join_variable(JoinVariable),
 2576        where_restriction_variable(JoinVariable)
 2577        <=>
 2578        throw(format('A variable used in a WHERE RESTRICTION must not also be a SHARED VARIABLE defining an OUTER JOIN point', [])).
 2579
 2580
 2581deprecated_group_by @
 2582        attribute_binding(_, attribute(_, _, group_by(_)), _)
 2583        <=>
 2584        throw(format('OBSOLETE group_by format.  Use separate group_by([V1, V2, ...])', [])).
 2585
 2586
 2587bad_group_by_specification @
 2588        group_bys(_, GroupBys)
 2589        <=>
 2590        ( \+ is_list(GroupBys)
 2591        ; is_list(GroupBys),
 2592          member(GroupBy, GroupBys),
 2593          nonvar(GroupBy)
 2594        )
 2595        |
 2596        throw(format('GROUP BY must specify a LIST of variables', [group_by(GroupBys)])).
 2597
 2598
 2599individual_group_by @
 2600        group_bys(QueryId, [GroupBy|GroupBys])
 2601        <=>
 2602        group_by(QueryId, GroupBy),
 2603        group_bys(QueryId, GroupBys).
 2604
 2605
 2606no_more_group_bys @
 2607        group_bys(_, [])
 2608        <=>
 2609        true.
 2610
 2611
 2612copy_attribute_for_group_by @
 2613        attribute_binding(QueryId, attribute(_, TableAlias, AttributeName), Variable)
 2614        ==>
 2615        attribute_for_group_by(QueryId, TableAlias, AttributeName, Variable).
 2616
 2617
 2618ambiguous_group_by_attribute @
 2619        group_by(QueryId, GroupBy),
 2620        attribute_for_group_by(QueryId, TableAliasA, AttributeNameA, GroupBy),
 2621        attribute_for_group_by(QueryId, TableAliasB, AttributeNameB, GroupBy),
 2622        query_table_alias(_, _, TableNameA, TableAliasA),
 2623        query_table_alias(_, _, TableNameB, TableAliasB)
 2624        <=>
 2625        throw(format('GROUP BY variable is AMBIGUOUS.  It identifies both ~w.~w AND ~w.~w.  Use == to specify the join point?',
 2626                     [TableNameA, AttributeNameA, TableNameB, AttributeNameB])).
 2627
 2628
 2629bad_distinct_specification @
 2630        distincts(_, Distincts)
 2631        <=>
 2632        ( \+ is_list(Distincts)
 2633        ; is_list(Distincts),
 2634          member(Distinct, Distincts),
 2635          nonvar(Distinct)
 2636        )
 2637        |
 2638        throw(format('DISTINCT must specify a LIST of variables', [distinct(Distincts)])).
 2639
 2640
 2641individual_distinct @
 2642        distincts(QueryId, [Distinct|Distincts])
 2643        <=>
 2644        distinct(QueryId, Distinct),
 2645        distincts(QueryId, Distincts).
 2646
 2647
 2648no_more_distincts @
 2649        distincts(QueryId, [])
 2650        <=>
 2651        select_distinction(QueryId, distinct_on_specified_attributes).
 2652
 2653
 2654determine_select_distinctions @
 2655        query(QueryId, _, _),
 2656        determine_select_distinctions
 2657        ==>
 2658        determine_select_distinction(QueryId).
 2659
 2660
 2661select_distinction_exists @
 2662        select_distinction(QueryId, _)
 2663        \
 2664        determine_select_distinction(QueryId)
 2665        <=>
 2666        true.
 2667
 2668
 2669no_select_distinction @
 2670        determine_select_distinction(QueryId)
 2671        <=>
 2672        select_distinction(QueryId, no_distinction).
 2673
 2674
 2675select_binding @
 2676        create_select_bindings,
 2677        attribute_binding(QueryId, attribute(Schema, TableAlias, AttributeName), Variable)
 2678        ==>
 2679        selection_variable(Variable)
 2680        |
 2681        Attribute = attribute(Schema, TableAlias, AttributeName),
 2682        select_binding(QueryId, plain, Attribute, Variable).
 2683
 2684cleanup_create_select_bindings @
 2685        create_select_bindings
 2686        <=>
 2687        true.
 2688
 2689
 2690selection_variable(V) :-
 2691        var(V).
 2692selection_variable(V) :-
 2693        \+ ground(V),
 2694        cql_atomic_value_check_hook(V).
 2695selection_variable(selection_constant(_)).
 2696
 2697
 2698select_binding_aggregation @
 2699        select_binding(QueryId, plain, attribute(Schema, TableAlias, AggregationTerm), Variable)
 2700        <=>
 2701        AggregationTerm =.. [AggregationOperator, AttributeName],
 2702        aggregation_operator(AggregationOperator)
 2703        |
 2704        select_binding(QueryId, aggregation(AggregationOperator), attribute(Schema, TableAlias, AttributeName), Variable).
 2705
 2706
 2707sub_select_binding_aggregation @
 2708        aggregation_variable(_, AggregationOperator, AggregationVariable),
 2709        select_binding(QueryId, plain, Attribute, Variable)
 2710        <=>
 2711        AggregationVariable == Variable
 2712        |
 2713        select_binding(QueryId, aggregation(AggregationOperator), Attribute, Variable).
 2714
 2715
 2716instantiate_table_aliases @
 2717        instantiate_table_aliases,
 2718        query_table_alias(_, _, TableName, TableAlias)
 2719        ==>
 2720        var(TableAlias)
 2721        |
 2722        table_alias_crunch(TableName, Crunched),
 2723        atom_concat(Crunched, '_', Stem),
 2724        gensym(Stem, Symbol),
 2725        map_database_atom(Symbol, TableAlias).
 2726
 2727
 2728table_alias_crunch(TableName, Crunched):-
 2729        atom_codes(TableName, Codes),
 2730        extract_abbreviation(AbbreviationCodes, [95|Codes], []),
 2731        atom_codes(Crunched, AbbreviationCodes).
 2732
 2733extract_abbreviation([])-->
 2734        [].
 2735
 2736extract_abbreviation([Code|Codes])-->
 2737        "_",
 2738        !,
 2739        [Code],
 2740        extract_abbreviation(Codes).
 2741
 2742extract_abbreviation(Codes)-->
 2743        [_],
 2744        extract_abbreviation(Codes).
 2745
 2746cleanup_instantiate_table_aliases @
 2747        instantiate_table_aliases
 2748        <=>
 2749        true.
 2750
 2751
 2752check_aggregation_attribute @
 2753        select_binding(QueryId, aggregation(_), attribute(Schema, TableAlias, AttributeName), _),
 2754        query_table_alias(QueryId, _, TableName, TableAlias)
 2755        <=>
 2756        \+ cql_data_type(Schema, TableName, AttributeName, _, _, _, _, _, _, _)
 2757        |
 2758        throw(format('Unknown SELECT attribute in CQL: ~w', [Schema:TableName:AttributeName])).
 2759
 2760
 2761aggregation_selection @
 2762        select_binding(QueryId, aggregation(_), _, _),
 2763        determine_selection_type
 2764        ==>
 2765        selection_type(QueryId, aggregation_selection).
 2766
 2767
 2768non_aggregation_selection @
 2769        select_binding(QueryId, SelectBindingType, _, _),
 2770        determine_selection_type
 2771        ==>
 2772        SelectBindingType \= aggregation(_)
 2773        |
 2774        selection_type(QueryId, non_aggregation_selection).
 2775
 2776
 2777cleanup_determine_selection_type @
 2778        determine_selection_type
 2779        <=>
 2780        true.
 2781
 2782
 2783priority @
 2784        selection_type(QueryId, aggregation_selection)
 2785        \
 2786        selection_type(QueryId, non_aggregation_selection)
 2787        <=>
 2788        true.
 2789
 2790
 2791uniqueness @
 2792        selection_type(QueryId, SelectionType)
 2793        \
 2794        selection_type(QueryId, SelectionType)
 2795        <=>
 2796        true.
 2797
 2798get_data_size(Schema, TableName, AttributeName, Size):-
 2799        cql_data_type(Schema, TableName, AttributeName, _, CharacterMaximumLength, _, _, _, _, _),
 2800        ( CharacterMaximumLength == max ->
 2801            % This should be close enough. It just has to be larger than any declared column length, and the max there is 8192 for SQL Server.
 2802            % For all other DBMS it doesnt matter
 2803            Size = 65535
 2804        ; integer(CharacterMaximumLength) ->
 2805            Size = CharacterMaximumLength
 2806        ; otherwise->
 2807            Size = 0
 2808        ).
 2809
 2810aggregation_selection @
 2811        selection_type(QueryId, aggregation_selection),
 2812        query_table_alias(QueryId, _, TableName, TableAlias)
 2813        \
 2814        select_binding(QueryId, SelectBindingType, attribute(Schema, TableAlias, AttributeName), Variable)
 2815        <=>
 2816        SelectBindingType = aggregation(_)
 2817        |
 2818        select_attribute(QueryId, select_attribute(SelectBindingType, Schema, TableName, TableAlias, AttributeName), _, _, Variable).
 2819
 2820
 2821aggregation_group_by_selection @
 2822        selection_type(QueryId, aggregation_selection),
 2823        query_table_alias(QueryId, _, TableName, TableAlias),
 2824        group_by(QueryId, GroupBy)
 2825        \
 2826        select_binding(QueryId, SelectBindingType, attribute(Schema, TableAlias, AttributeName), GroupBy)
 2827        <=>
 2828        select_attribute(QueryId, select_attribute(SelectBindingType, Schema, TableName, TableAlias, AttributeName), _, _, GroupBy).
 2829
 2830
 2831ignore_aggregation_select_binding @
 2832        selection_type(QueryId, aggregation_selection), where_restriction_variable(Variable) \ select_binding(QueryId, _, _, Variable) <=> true.
 2833        selection_type(QueryId, aggregation_selection), join_variable(Variable) \ select_binding(QueryId, _, _, Variable) <=> true.
 2834        selection_type(QueryId, aggregation_selection), sub_query_join_variable(Variable) \ select_binding(QueryId, _, _, Variable) <=> true.
 2835        selection_type(QueryId, aggregation_selection), ignore_if_null(_, Variable) \ select_binding(QueryId, _, _, Variable) <=> true.
 2836
 2837
 2838aggregation_select_binding_error @
 2839        check_for_orphan_select_attributes_in_aggregations,
 2840        selection_type(QueryId, aggregation_selection)
 2841        \
 2842        select_binding(QueryId, _, Attribute, _)
 2843        <=>
 2844        throw(format('Aggregation refers to an attribute which is not aggregated, not grouped by, not a restriction and not a join point: ~w', [Attribute])).
 2845
 2846
 2847non_aggregation_select_binding @
 2848        selection_type(QueryId, non_aggregation_selection),
 2849        query_table_alias(QueryId, _, TableName, TableAlias)
 2850        \
 2851        select_binding(QueryId, SelectBindingType, attribute(Schema, TableAlias, AttributeName), Variable)
 2852        <=>
 2853        select_attribute(QueryId, select_attribute(SelectBindingType, Schema, TableName, TableAlias, AttributeName), _, _, Variable).
 2854
 2855
 2856keep_if_distinct_on_specified_attributes @
 2857        select_distinction(QueryId, distinct_on_specified_attributes),
 2858        select_attribute(QueryId, _, Keep, _, Variable)
 2859        \
 2860        distinct(QueryId, Variable)
 2861        <=>
 2862        Keep = 1.
 2863
 2864
 2865keep_if_distinct_on_all_attributes_or_if_there_is_no_distinction @
 2866        select_distinction(QueryId, Distinction),
 2867        select_attribute(QueryId, _, Keep, _, _)
 2868        ==>
 2869        ( Distinction == distinct_on_all_select_attributes
 2870        ; Distinction == no_distinction
 2871        )
 2872        |
 2873        Keep = 1.
 2874
 2875
 2876copy_select_attribute_for_disjunction_comparison @
 2877        select_attribute(QueryId, select_attribute(SelectBindingType, Schema, TableName, TableAlias, AttributeName), _, _, _)
 2878        ==>
 2879        select_attribute_for_disjunction_comparison(QueryId, select_attribute(SelectBindingType, Schema, TableName, TableAlias, AttributeName)).
 2880
 2881
 2882bad_order_by_specification @
 2883        order_bys(_, OrderBys)
 2884        <=>
 2885        ( \+ is_list(OrderBys)
 2886        ; is_list(OrderBys),
 2887          member(OrderBy, OrderBys),
 2888          nonvar(OrderBy),
 2889          OrderBy \= +(_),
 2890          OrderBy \= -(_)
 2891        )
 2892        |
 2893        throw(format('ORDER BY must specify a LIST of +/1 and -/1 terms but found ~w', [order_by(OrderBys)])).
 2894
 2895
 2896copy_attribute_for_order_by @
 2897        attribute_binding(QueryId, attribute(_, TableAlias, AttributeName), Variable)
 2898        ==>
 2899        attribute_for_order_by(QueryId, TableAlias, AttributeName, Variable).
 2900
 2901
 2902ambiguous_order_by_attribute @
 2903        write_order_by(QueryId, OrderBy)
 2904        \
 2905        attribute_for_order_by(QueryId, TableAliasA, AttributeNameA, Variable),
 2906        attribute_for_order_by(QueryId, TableAliasB, AttributeNameB, Variable),
 2907        query_table_alias(_, _, TableNameA, TableAliasA),
 2908        query_table_alias(_, _, TableNameB, TableAliasB)
 2909        <=>
 2910        ( OrderBy == +Variable
 2911        ; OrderBy == -Variable
 2912        )
 2913        |
 2914        throw(format('ORDER BY variable is AMBIGUOUS.  It identifies both ~w.~w AND ~w.~w.  Use == to specify the join point?',
 2915                     [TableNameA, AttributeNameA, TableNameB, AttributeNameB])).
 2916
 2917select_attributes_1 @
 2918        selection_type(QueryId, _)
 2919        ==>
 2920        select_attributes_for_disjunction_comparison(QueryId, []).
 2921
 2922
 2923select_attributes_2 @
 2924        select_attribute_for_disjunction_comparison(QueryId, SelectAttribute),
 2925        select_attributes_for_disjunction_comparison(QueryId, SelectAttributes)
 2926        <=>
 2927        merge_set([SelectAttribute], SelectAttributes, SortedSelectAttributes),
 2928        select_attributes_for_disjunction_comparison(QueryId, SortedSelectAttributes).
 2929
 2930
 2931check_for_top_without_order_by @
 2932        top(QueryId, _, _), order_bys(QueryId, _) \ check_for_top_without_order_by <=> true.
 2933        top(_, _, _), check_for_top_without_order_by, original_cql(Cql) <=> throw(format('top without order_by in CQL: ~w', [Cql])).
 2934        check_for_top_without_order_by <=> true.
 2935
 2936
 2937join_tree_nodes @
 2938        simplify,
 2939        query(Join, _, top_level_query)       % Only bother doing join_tree for top_level_queries
 2940        % Solitary join leaf has the QueryId as its parent i.e. Join == QueryId
 2941        ==>
 2942        join_pointer(Join, Join),
 2943        join_tree_nodes(Join, []).
 2944
 2945
 2946identify_join_type_1 @
 2947        join(_, _, _, 'LEFT OUTER JOIN', RhsJoin)
 2948        ==>
 2949        outer_side_join(RhsJoin).
 2950
 2951
 2952identify_join_type_2 @
 2953        join(_, _, LhsJoin, 'RIGHT OUTER JOIN', _)
 2954        ==>
 2955        outer_side_join(LhsJoin).
 2956
 2957
 2958every_join_below_an_outer_side_join_is_an_outer_side_join @
 2959        outer_side_join(ParentJoin),
 2960        join(_, ParentJoin, LhsJoin, _, RhsJoin)
 2961        ==>
 2962        outer_side_join(LhsJoin),
 2963        outer_side_join(RhsJoin).
 2964
 2965
 2966walk_join_tree_branch @
 2967        join(QueryId, Join, LhsJoin, JoinType, RhsJoin)
 2968        \
 2969        join_pointer(QueryId, Join)
 2970        <=>
 2971        join_tree_node(QueryId, Join, branch(JoinType)),
 2972        join_pointer(QueryId, LhsJoin),
 2973        join_pointer(QueryId, RhsJoin).
 2974
 2975
 2976walk_join_tree_on_clause @
 2977        join_tree_node(QueryId, Join, branch(_)),
 2978        on(Join, _, On)
 2979        ==>
 2980        join_tree_node(QueryId, Join, On).
 2981
 2982
 2983cleanup_join_tree_node_branch @
 2984        join_tree_node(_, _, branch(_))
 2985        <=>
 2986        true.
 2987
 2988
 2989walk_join_tree_leaf @
 2990        join_leaf(Join, TableAlias),
 2991        query_table_alias(QueryId, _, _, TableAlias)
 2992        \
 2993        join_pointer(QueryId, Join)
 2994        <=>
 2995        join_tree_node(QueryId, Join, table_alias(TableAlias)).
 2996
 2997
 2998accumulate_join_tree_nodes @
 2999        join_tree_nodes(QueryId, JoinTreeNodes),
 3000        join_tree_node(QueryId, _, JoinTreeNode)
 3001        <=>
 3002        join_tree_nodes(QueryId, [JoinTreeNode|JoinTreeNodes]).
 3003
 3004
 3005amalgamate_restrictions_if_join_tree_is_the_same @
 3006        select_attributes_for_disjunction_comparison(QueryIdA, SelectAttributesA),
 3007        join_tree_nodes(QueryIdA, JoinTreeNodesA)
 3008        \
 3009        select_attributes_for_disjunction_comparison(QueryIdB, SelectAttributesB),
 3010        join_tree_nodes(QueryIdB, JoinTreeNodesB),
 3011        restriction_tree(QueryIdA, RestrictionType, RestrictionTreeA),
 3012        restriction_tree(QueryIdB, RestrictionType, RestrictionTreeB)
 3013        <=>
 3014        unifiable(SelectAttributesA, SelectAttributesB, _),
 3015        unifiable(JoinTreeNodesA, JoinTreeNodesB, Unifiers)
 3016        |
 3017        restriction_tree(QueryIdA, RestrictionType, or(RestrictionTreeA, RestrictionTreeB)),
 3018        remove_query(QueryIdB, QueryIdA),
 3019        unify_table_aliases(Unifiers).
 3020
 3021
 3022% We can do this because the ONLY unbound variables in the join tree are table aliases
 3023unify_table_aliases([]).
 3024unify_table_aliases([TableAliasA=TableAliasB|Unifiers]) :-
 3025        TableAliasA = TableAliasB,
 3026        unify_table_aliases(Unifiers).
 3027
 3028
 3029solve_sub_query @
 3030        generate_sub_query_sql,
 3031        query(SubQueryId, _, sub_query)
 3032        ==>
 3033        phase(SubQueryId, initial).
 3034
 3035
 3036solve_top_level_query @
 3037        write_query_sql,
 3038        query(QueryId, _, top_level_query)
 3039        ==>
 3040        phase(QueryId, initial).
 3041
 3042
 3043ignore_equality_restriction_variable_if_it_becomes_bound @
 3044        equality_restriction_variable(Variable, _)
 3045        <=>
 3046        nonvar(Variable)
 3047        |
 3048        true.
 3049
 3050
 3051add_sub_query_join_where @
 3052        query(TopLevelQueryId, _, top_level_query),
 3053        query(SubQueryId, _, sub_query),
 3054        attribute_binding(TopLevelQueryId, attribute(_, TopLevelTableAlias, TopLevelAttributeName), Variable),
 3055        attribute_binding(SubQueryId, attribute(_, SubQueryTableAlias, SubQueryAttributeName), Variable)
 3056        \
 3057        % No longer a SELECT binding in the sub-query; its now part of the sub query WHERE
 3058        select_binding(SubQueryId, _, _, Variable)
 3059        <=>
 3060        not_a_singleton(Variable),
 3061        sub_query_join_variable(Variable),
 3062        restriction_leaf(SubQueryId,
 3063                         where,
 3064                         comparison(attribute(_, TopLevelTableAlias, TopLevelAttributeName),
 3065                                    ==,
 3066                                    attribute(_, SubQueryTableAlias, SubQueryAttributeName))).
 3067
 3068
 3069restriction_from_comparison_of_top_level_query_attribute_to_sub_query_attribute @
 3070        %
 3071        % x :: [a-A, b-B], \+ y :: [b-B, c-C], C > A
 3072        %
 3073        query(QueryId, _, top_level_query),
 3074        query(SubQueryId, _, sub_query),
 3075        attribute_binding(QueryId, Attribute_1, V1),
 3076        attribute_binding(SubQueryId, Attribute_2, V2)
 3077        \
 3078        comparison(QueryId, Lhs, Operator, Rhs)
 3079        <=>
 3080        ( Lhs == V1,
 3081          Rhs == V2 ->
 3082            Comparison = comparison(Attribute_1, Operator, Attribute_2)
 3083
 3084        ; Lhs == V2,
 3085          Rhs == V1 ->
 3086            Comparison = comparison(Attribute_2, Operator, Attribute_1)
 3087        )
 3088        |
 3089        restriction_leaf(SubQueryId, where, Comparison).
 3090
 3091
 3092add_sub_query_restriction @
 3093        create_restrictions
 3094        \
 3095        sub_query_restriction(QueryId, SubQueryType, SubQuerySql, SubQueryTail, SubQueryInputs)
 3096        <=>
 3097        restriction_leaf(QueryId, where, sub_query(SubQueryType, SubQuerySql, SubQueryTail, SubQueryInputs)).
 3098
 3099
 3100restriction_from_bound_attribute @
 3101        %
 3102        % x :: a-'A1'
 3103        % x :: a-['A1', 'A2']
 3104        %
 3105        create_restrictions,
 3106        attribute_binding(QueryId, Attribute, ApplicationValue)
 3107        ==>
 3108        ( ground(ApplicationValue)
 3109        ; is_list(ApplicationValue)
 3110        ),
 3111        ApplicationValue \= selection_constant(_)
 3112        |
 3113        restriction_leaf(QueryId, where, comparison(Attribute, ==, ApplicationValue)).
 3114
 3115
 3116restriction_from_equality_restriction_variable @
 3117        %
 3118        % {[A], x :: [a-A]}
 3119        %
 3120        create_restrictions,
 3121        attribute_binding(QueryId, Attribute, Variable),
 3122        equality_restriction_variable(Variable, EqualityRestrictionVariableUsed)
 3123        ==>
 3124        EqualityRestrictionVariableUsed = equality_restriction_variable_used,
 3125        where_restriction_variable(Variable),
 3126        restriction_leaf(QueryId, where, comparison(Attribute, ==, equality_restriction(Variable))).
 3127
 3128
 3129restriction_from_comparison @
 3130        create_restrictions
 3131        \
 3132        comparison(QueryId, Lhs, Operator, Rhs)
 3133        <=>
 3134        not_a_singleton(Lhs),
 3135        not_a_singleton(Rhs),
 3136        variables_to_attributes(Lhs, MappedLhs),
 3137        variables_to_attributes(Rhs, MappedRhs),
 3138        restriction_leaf(QueryId, where, comparison(MappedLhs, Operator, MappedRhs)).
 3139
 3140cqlv2_1_restriction_from_any_non_fresh_variable @
 3141        query_type(QueryId, QueryType),
 3142        compile_mode(compiletime),
 3143        attribute_binding(QueryId, attribute(Schema, Alias, AttributeName), Variable)
 3144        ==>
 3145        atom(AttributeName), % Exclude aggregates. Is there a more elegant way?
 3146        var(Variable),
 3147        get_attr(Variable, cql_stale, 1)
 3148        |
 3149        ( ( QueryType == select ; QueryType == insert) ->
 3150            Comparison = if_not_var(Variable)
 3151        ; otherwise->
 3152            Comparison = equality_restriction(Variable)
 3153        ),
 3154        cql2_variable(QueryId, Variable, comparison(attribute(Schema, Alias, AttributeName), ==, Comparison)).
 3155
 3156/*
 3157cqlv2_variable_unique @
 3158        cql2_variable(QueryId, _, Variable)
 3159        \
 3160        cql2_variable(QueryId, _, Variable)
 3161        <=>
 3162        true.
 3163*/
 3164
 3165cqlv2_1_except_when_restriction_already_exists_1 @
 3166        equality_restriction_variable(Variable, _)
 3167        \
 3168        cql2_variable(_, Variable, _)
 3169        <=>
 3170        true.
 3171
 3172cqlv2_1_except_when_restriction_already_exists_2 @
 3173        expression_where_restriction_variable(Variable)
 3174        \
 3175        cql2_variable(_, Variable, _)
 3176        <=>
 3177        true.
 3178
 3179cqlv2_1_except_when_restriction_already_exists_3 @
 3180        sub_query_join_variable(Variable)
 3181        \
 3182        cql2_variable(_, Variable, _)
 3183        <=>
 3184        true.
 3185
 3186cqlv2_1_except_when_restriction_already_exists_4 @
 3187        expression_where_restriction_variable(Variable)
 3188        \
 3189        cql2_variable(_, Variable, _)
 3190        <=>
 3191        true.
 3192
 3193cqlv2_1_except_when_restriction_already_exists_5 @
 3194        outer_side_join(Join),
 3195        join_leaf(Join, TableAlias),
 3196        attribute_binding(_, attribute(_, TableAlias, _), JoinVariable),
 3197        join_variable(JoinVariable)
 3198        \
 3199        cql2_variable(_, JoinVariable, _)
 3200        <=>
 3201        true.
 3202
 3203
 3204cqlv2_1_except_comparisons @
 3205        query_type(QueryId, Type),
 3206        comparison(QueryId, Lhs, _Operator, Rhs)
 3207        \
 3208        cql2_variable(QueryId, Variable, _)
 3209        <=>
 3210        % If you write something like
 3211        % foo(X):- {[], some_table :: [column-X], X == 'VALUE'}
 3212        % Then, first of all, you probably made a coding error, since this is unlikely what you meant.
 3213        % X is not actually selected here, it MUST be part of the where clause. Further, it MUST contain 'VALUE'.
 3214        % For now, unify X with the target (Value). However, we must do it after the select. Consider:
 3215        % foo(X):- {[], some_table :: [integer_value-X], X > 500}
 3216        % This should generate
 3217        %   SELECT .... FROM some_table WHERE integer_value > 500
 3218        % What should we actually do with X? If it is bound, then we can make it
 3219        %    SELECT .... FROM some_table WHERE integer_value > 500 AND integer_value = ?
 3220        % If it is NOT bound, then I think this is actually an instantiation error?
 3221        % The trouble comes when we have
 3222        % {[], update(some_table, [...]), @ :: [integer_value-X], X == Y}.
 3223        %   If Y is unbound here, we want a runtime error, but if X is bound, we want an error as well!
 3224        ( Type == update ; Type == delete ),
 3225        ( Lhs == Variable ; Rhs == Variable )
 3226        |
 3227        runtime_instantiation_check(QueryId, Variable).
 3228
 3229
 3230cqlv2_variable_is_ok @
 3231        create_restrictions
 3232        \
 3233        cql2_variable(QueryId, Variable, Comparison)
 3234        <=>
 3235        where_restriction_variable(Variable),
 3236        restriction_leaf(QueryId, where, Comparison).
 3237
 3238
 3239
 3240
 3241
 3242
 3243variables_to_attributes @
 3244        attribute_binding(_, A, Variable) \ variables_to_attributes(Variable, Attribute) <=> var(Variable) | Attribute = A, where_restriction_variable(Variable).
 3245        variables_to_attributes(T1, T2) <=> var(T1) ; ground(T1) | T2 = T1.
 3246        variables_to_attributes([H1|T1], T3) <=> variables_to_attributes(H1, H2), variables_to_attributes(T1, T2), T3 = [H2|T2].
 3247        variables_to_attributes(T1, T4) <=> T1 =.. T2, variables_to_attributes(T2, T3), T4 =.. T3.
 3248
 3249
 3250cleanup_create_restrictions @
 3251        create_restrictions
 3252        <=>
 3253        true.
 3254
 3255
 3256ignore_comparison_to_empty_list @
 3257        restriction_leaf(_, _, comparison(Lhs, ==, Rhs))
 3258        <=>
 3259        ( Lhs == []
 3260        ; Rhs == []
 3261        )
 3262        |
 3263        true.
 3264
 3265
 3266top_level_restriction_cannot_refer_to_a_sub_query_attribute @
 3267        query(TopLevelQueryId, _, top_level_query),
 3268        query(SubQueryId, _, sub_query),
 3269        attribute_binding(SubQueryId, attribute(Schema, TableAlias, AttributeName), _)
 3270        \
 3271        restriction_leaf(TopLevelQueryId, _, comparison(Lhs, _, Rhs))
 3272        <=>
 3273        ( cql_path_arg(_, Lhs, SubTerm)
 3274        ; cql_path_arg(_, Rhs, SubTerm)),
 3275        SubTerm == attribute(Schema, TableAlias, AttributeName)
 3276        |
 3277        throw(format('Top level restriction cannot refer to a sub-query attribute : ~w', [AttributeName])).
 3278
 3279
 3280simplify_or_restriction @
 3281        % Trivial "or" conditions can arise out from the simplification of disjunctions
 3282        restriction_tree(QueryId, RestrictionType, or(Lhs, Rhs))
 3283        <=>
 3284        ( Lhs == true
 3285        ; Rhs == true
 3286        )
 3287        |
 3288        restriction_tree(QueryId, RestrictionType, true).
 3289
 3290
 3291simplify_and_restriction @
 3292        restriction_tree(QueryId, RestrictionType, and(Lhs, Rhs))
 3293        <=>
 3294        ( Lhs == true ->
 3295            RestrictionTree = Rhs
 3296
 3297        ; Rhs == true ->
 3298            RestrictionTree = Lhs
 3299        )
 3300        |
 3301        restriction_tree(QueryId, RestrictionType, RestrictionTree).
 3302
 3303
 3304add_to_restriction_tree @
 3305        restriction_tree(QueryId, RestrictionType, ExistingRestrictionTree),
 3306        restriction_leaf(QueryId, RestrictionType, Restriction)
 3307        <=>
 3308        restriction_tree(QueryId, RestrictionType, and(ExistingRestrictionTree, Restriction)).
 3309
 3310
 3311insert_inserted_ @
 3312        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3313        <=>
 3314        cql_data_type(Schema, TableName, inserted_, _, _, _, _, _, _, _),
 3315        \+ memberchk(inserted_-_, AttributeNameValuePairs)
 3316        |
 3317        insert(QueryId, Schema, TableName, [inserted_-{timestamp}|AttributeNameValuePairs]).
 3318
 3319
 3320insert_inserted_by_ @
 3321        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3322        <=>
 3323        cql_data_type(Schema, TableName, inserted_by_, _, _, _, _, _, _, _),
 3324        \+ memberchk(inserted_by_-_, AttributeNameValuePairs)
 3325        |
 3326        insert(QueryId, Schema, TableName, [inserted_by_-{user_id}|AttributeNameValuePairs]).
 3327
 3328
 3329insert_updated_ @
 3330        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3331        <=>
 3332        cql_data_type(Schema, TableName, updated_, _, _, _, _, _, _, _),
 3333        \+ memberchk(updated_-_, AttributeNameValuePairs)
 3334        |
 3335        insert(QueryId, Schema, TableName, [updated_-{timestamp}|AttributeNameValuePairs]).
 3336
 3337
 3338insert_updated_by_ @
 3339        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3340        <=>
 3341        cql_data_type(Schema, TableName, updated_by_, _, _, _, _, _, _, _),
 3342        \+ memberchk(updated_by_-_, AttributeNameValuePairs)
 3343        |
 3344        insert(QueryId, Schema, TableName, [updated_by_-{user_id}|AttributeNameValuePairs]).
 3345
 3346
 3347update_updated_ @
 3348        update(QueryId, Schema, TableName, TableAlias, AttributeNameValuePairs)
 3349        <=>
 3350        cql_data_type(Schema, TableName, updated_, _, _, _, _, _, _, _),
 3351        \+ memberchk(updated_-_, AttributeNameValuePairs)
 3352        |
 3353        update(QueryId, Schema, TableName, TableAlias, [updated_-{timestamp}|AttributeNameValuePairs]).
 3354
 3355
 3356update_updated_by_ @
 3357        update(QueryId, Schema, TableName, TableAlias, AttributeNameValuePairs)
 3358        <=>
 3359        cql_data_type(Schema, TableName, updated_by_, _, _, _, _, _, _, _),
 3360        \+ memberchk(updated_by_-_, AttributeNameValuePairs)
 3361        |
 3362        update(QueryId, Schema, TableName, TableAlias, [updated_by_-{user_id}|AttributeNameValuePairs]).
 3363
 3364
 3365insert_transaction_id_ @
 3366        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3367        <=>
 3368        cql_data_type(Schema, TableName, transaction_id_, _, _, _, _, _, _, _),
 3369        \+ memberchk(transaction_id_-_, AttributeNameValuePairs)
 3370        |
 3371        insert(QueryId, Schema, TableName, [transaction_id_-{transaction_id}|AttributeNameValuePairs]).
 3372
 3373
 3374update_transaction_id_ @
 3375        update(QueryId, Schema, TableName, TableAlias, AttributeNameValuePairs)
 3376        <=>
 3377        cql_data_type(Schema, TableName, transaction_id_, _, _, _, _, _, _, _),
 3378        \+ memberchk(transaction_id_-_, AttributeNameValuePairs)
 3379        |
 3380        update(QueryId, Schema, TableName, TableAlias, [transaction_id_-{transaction_id}|AttributeNameValuePairs]).
 3381
 3382
 3383insert_generation_ @
 3384        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3385        <=>
 3386        cql_data_type(Schema, TableName, generation_, _, _, _, _, _, _, _),
 3387        \+ memberchk(generation_-_, AttributeNameValuePairs)
 3388        |
 3389        insert(QueryId, Schema, TableName, [generation_-0|AttributeNameValuePairs]).
 3390
 3391
 3392update_generation_ @
 3393        update(QueryId, Schema, TableName, TableAlias, AttributeNameValuePairs)
 3394        <=>
 3395        cql_data_type(Schema, TableName, generation_, _, _, _, _, _, _, _),
 3396        \+ memberchk(generation_-_, AttributeNameValuePairs)
 3397        |
 3398        update(QueryId, Schema, TableName, TableAlias, [generation_-{increment}|AttributeNameValuePairs]).
 3399
 3400
 3401write_insert_based_on_select @
 3402        query_table_alias(QueryId, _, _, _),
 3403        phase(QueryId, initial)
 3404        \
 3405        insert(QueryId, _, TableName, AttributeNameValuePairs)
 3406        <=>
 3407        extract_variables(AttributeNameValuePairs, InsertVariables),
 3408        select_for_insert_variables(InsertVariables, TableName),
 3409        write_sql(QueryId, compile, top, ['INSERT INTO ', table_name(TableName), ' ('|T1], T1, [], []),
 3410        write_insert_attribute_names(QueryId, AttributeNameValuePairs),
 3411        write_sql(QueryId, compile, top, [') '|T2], T2, [], []).
 3412
 3413
 3414
 3415extract_variables([], []).
 3416
 3417extract_variables([_-V|AttributeNameValuePairs], [V|InsertVariables]) :-
 3418        var(V), !,
 3419        extract_variables(AttributeNameValuePairs, InsertVariables).
 3420
 3421extract_variables([_|AttributeNameValuePairs], InsertVariables) :-
 3422        extract_variables(AttributeNameValuePairs, InsertVariables).
 3423
 3424
 3425write_insert @
 3426        phase(QueryId, initial),
 3427        insert(QueryId, Schema, TableName, AttributeNameValuePairs)
 3428        <=>
 3429        ( AttributeNameValuePairs == []->
 3430            write_sql(QueryId, compile, top, ['INSERT INTO ', table_name(TableName), ' DEFAULT VALUES'|T1], T1, [], [])
 3431        ;
 3432            write_sql(QueryId, compile, top, ['INSERT INTO ', table_name(TableName), ' ('|T2], T2, [], []),
 3433            write_insert_attribute_names(QueryId, AttributeNameValuePairs),
 3434            write_sql(QueryId, compile, top, [') VALUES ('|T3], T3, [], []),
 3435            write_insert_values(QueryId, Schema, TableName, AttributeNameValuePairs),
 3436            ( dbms(Schema, 'PostgreSQL'),
 3437              database_identity(Schema, TableName, PrimaryKey) ->
 3438                write_sql(QueryId, compile, top, [') RETURNING ', PrimaryKey|T4], T4, [], [])
 3439            ; otherwise->
 3440                write_sql(QueryId, compile, top, [')'|T4], T4, [], [])
 3441            )
 3442        ).
 3443
 3444
 3445write_insert_attribute_names_1 @
 3446        write_insert_attribute_names(QueryId, [AttributeName-_])
 3447        <=>
 3448        write_insert_attribute_name(QueryId, AttributeName).
 3449
 3450
 3451write_insert_attribute_names_2 @
 3452        write_insert_attribute_names(QueryId, [AttributeName-_|AttributeNameValuePairs])
 3453        <=>
 3454        write_insert_attribute_name(QueryId, AttributeName),
 3455        write_sql(QueryId, compile, top, [', '|T], T, [], []),
 3456        write_insert_attribute_names(QueryId, AttributeNameValuePairs).
 3457
 3458
 3459write_insert_attribute_name @
 3460        write_insert_attribute_name(QueryId, AttributeName)
 3461        <=>
 3462        write_sql(QueryId, compile, top, [attribute_name(AttributeName)|T], T, [], []).
 3463
 3464
 3465write_insert_values_1 @
 3466        write_insert_values(QueryId, Schema, TableName, [AttributeName-ApplicationValue])
 3467        <=>
 3468        write_insert_value(QueryId, Schema, TableName, AttributeName, ApplicationValue).
 3469
 3470
 3471write_insert_values_2 @
 3472        write_insert_values(QueryId, Schema, TableName, [AttributeName-ApplicationValue|AttributeNameValuePairs])
 3473        <=>
 3474        write_insert_value(QueryId, Schema, TableName, AttributeName, ApplicationValue),
 3475        write_sql(QueryId, compile, top, [', '|T], T, [], []),
 3476        write_insert_values(QueryId, Schema, TableName, AttributeNameValuePairs).
 3477
 3478
 3479write_in_line_formatted_insert_value @
 3480        write_insert_value(QueryId, Schema, TableName, AttributeName, format(Format, FormatArgs))
 3481        <=>
 3482        in_line_format(QueryId, Format, FormatArgs, ApplicationValue),
 3483        write_insert_value(QueryId, Schema, TableName, AttributeName, ApplicationValue).
 3484
 3485
 3486write_insert_value @
 3487        write_insert_value(QueryId, Schema, TableName, AttributeName, ApplicationValue)
 3488        <=>
 3489        write_sql(QueryId, compile, top, [?|T], T, [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, insert_value, _)], []).
 3490
 3491
 3492write_update @
 3493        update(QueryId, Schema, TableName, TableAlias, AttributeNameValuePairs)
 3494        \
 3495        phase(QueryId, initial)
 3496        <=>
 3497        ( dbms(Schema, 'Microsoft SQL Server') ->
 3498            write_sql(QueryId, compile, top, ['UPDATE ', TableAlias, ' SET '|T], T, [], [])
 3499
 3500        ; dbms(Schema, 'PostgreSQL') ->
 3501            write_sql(QueryId, compile, top, ['UPDATE ', TableName, ' ', TableAlias, ' SET '|T], T, [], [])
 3502        ; dbms(Schema, 'SQLite') ->
 3503            % SQLite does not support joins in updates. However, it has an ID for each row, meaning we can put this:
 3504            % UPDATE <tablename> SET <columns without aliases> WHERE rowid IN (SELECT <tablename>.rowid FROM <rest of the query>)
 3505            write_sql(QueryId, compile, top, ['UPDATE ', TableName, ' SET '|T], T, [], [])
 3506        ),
 3507        write_update_attributes(QueryId, TableAlias, AttributeNameValuePairs),
 3508        phase(QueryId, from).
 3509
 3510
 3511write_update_attributes_1 @
 3512        write_update_attributes(QueryId, TableAlias, [AttributeName-ApplicationValue])
 3513        <=>
 3514        write_update_attribute(QueryId, TableAlias, AttributeName, ApplicationValue).
 3515
 3516
 3517write_update_attributes_2 @
 3518        write_update_attributes(QueryId, TableAlias, [AttributeName-ApplicationValue|AttributeNameValuePairs])
 3519        <=>
 3520        write_update_attribute(QueryId, TableAlias, AttributeName, ApplicationValue),
 3521        write_sql(QueryId, compile, top, [', '|T], T, [], []),
 3522        write_update_attributes(QueryId, TableAlias, AttributeNameValuePairs).
 3523
 3524
 3525write_update_attributes_3 @
 3526        write_update_attributes(_, _, AttributeNameValuePairs)
 3527        <=>
 3528        throw(format('Bad UPDATE attributes: ~w',  [AttributeNameValuePairs])).
 3529
 3530
 3531write_generation_attribute @
 3532        update_table_alias(QueryId, Schema, _, TableAlias)
 3533        \
 3534        write_update_attribute(QueryId, TableAlias, AttributeName, {increment})
 3535        <=>
 3536        AttributeName == generation_
 3537        |
 3538        ( dbms(Schema, 'Microsoft SQL Server') ->
 3539            write_sql(QueryId,
 3540                      compile,
 3541                      top,
 3542                      [TableAlias, '.', attribute_name(AttributeName), =, TableAlias, '.', attribute_name(AttributeName), +, '1'|T],
 3543                      T,
 3544                      [],
 3545                      [])
 3546        ; dbms(Schema, 'PostgreSQL') ->
 3547            write_sql(QueryId, compile,
 3548                      top,
 3549                      [attribute_name(AttributeName), =, TableAlias, '.', attribute_name(AttributeName), +, '1'|T],
 3550                      T,
 3551                      [],
 3552                      [])
 3553        ; dbms(Schema, 'SQLite') ->
 3554            write_sql(QueryId, compile,
 3555                      top,
 3556                      [attribute_name(AttributeName), =, attribute_name(AttributeName), +, '1'|T],
 3557                      T,
 3558                      [],
 3559                      [])
 3560        ).
 3561
 3562
 3563write_update_attribute_copy_sql_server @
 3564        query_table_alias(QueryId, Schema, _, TableAlias),
 3565        select_attribute(QueryId, select_attribute(_, _, _, SelectTableAlias, SelectAttributeName), 1, SelectAttributeVariableUsed, SelectVariable)
 3566        \
 3567        write_update_attribute(QueryId, TableAlias, AttributeName, UpdateVariable)
 3568        <=>
 3569        dbms(Schema, 'Microsoft SQL Server'),
 3570        var(SelectVariable),
 3571        SelectVariable == UpdateVariable
 3572        |
 3573        SelectAttributeVariableUsed = select_attribute_variable_used,
 3574        write_sql(QueryId,
 3575                  compile,
 3576                  top,
 3577                  [TableAlias, '.', attribute_name(AttributeName), =, SelectTableAlias, '.', attribute_name(SelectAttributeName)|T],
 3578                  T,
 3579                  [],
 3580                  []).
 3581
 3582write_update_attribute_copy_postgres @
 3583        update_table_alias(QueryId, Schema, _, TargetAlias),
 3584        query_table_alias(QueryId, _, _, TableAlias),
 3585        select_attribute(QueryId, select_attribute(_, _, _, SelectTableAlias, SelectAttributeName), 1, SelectAttributeVariableUsed, SelectVariable)
 3586        \
 3587        write_update_attribute(QueryId, TableAlias, AttributeName, UpdateVariable)
 3588        <=>
 3589        dbms(Schema, 'PostgreSQL'),
 3590        var(SelectVariable),
 3591        SelectVariable == UpdateVariable
 3592        |
 3593        SelectAttributeVariableUsed = select_attribute_variable_used,
 3594
 3595        ( TargetAlias == TableAlias ->
 3596            write_sql(QueryId,
 3597                      compile,
 3598                      top,
 3599                      [attribute_name(AttributeName), =, SelectTableAlias, '.', attribute_name(SelectAttributeName)|T],
 3600                      T,
 3601                      [],
 3602                      [])
 3603        ; otherwise->
 3604            write_sql(QueryId,
 3605                      compile,
 3606                      top,
 3607                      [TableAlias, '.', attribute_name(AttributeName), =, SelectTableAlias, '.', attribute_name(SelectAttributeName)|T],
 3608                      T,
 3609                      [],
 3610                      [])
 3611
 3612        ).
 3613
 3614
 3615write_update_attribute_copy_sqlite @
 3616        update_table_alias(QueryId, Schema, _, TargetAlias),
 3617        query_table_alias(QueryId, Schema, TableName, TableAlias),
 3618        select_attribute(QueryId, select_attribute(_, _, _, SelectTableAlias, SelectAttributeName), 1, SelectAttributeVariableUsed, SelectVariable)
 3619        \
 3620        write_update_attribute(QueryId, TableAlias, AttributeName, UpdateVariable)
 3621        <=>
 3622        dbms(Schema, 'SQLite'),
 3623        var(SelectVariable),
 3624        SelectVariable == UpdateVariable
 3625        |
 3626        SelectAttributeVariableUsed = select_attribute_variable_used,
 3627        ( TargetAlias == SelectTableAlias->
 3628            % This is the simplest case. Otherwise we must write a subquery
 3629            write_sql(QueryId,
 3630                      compile,
 3631                      top,
 3632                      [attribute_name(AttributeName), =, attribute_name(SelectAttributeName)|T],
 3633                      T,
 3634                      [],
 3635                      [])
 3636        ; otherwise->
 3637            write_sql(QueryId,
 3638                      compile,
 3639                      top,
 3640                      [attribute_name(AttributeName), =, '(SELECT ', SelectTableAlias, '.', attribute_name(SelectAttributeName), ' '|T],
 3641                      T,
 3642                      [],
 3643                      []),
 3644          Tail = [' AND ', TableAlias, '.rowid = ', TableName, '.rowid)'|T3],
 3645          write_sql(QueryId,
 3646                    compile,
 3647                    top,
 3648                    X,
 3649                    T3,
 3650                    Parameters,
 3651                    []),
 3652          find_copy_of_from(QueryId, X, Tail, Parameters)
 3653        ).
 3654
 3655write_in_line_formatted_update_attribute @
 3656        query_table_alias(QueryId, _, _, TableAlias)
 3657        \
 3658        write_update_attribute(QueryId, TableAlias, AttributeName, format(Format, FormatArgs))
 3659        <=>
 3660        in_line_format(QueryId, Format, FormatArgs, ApplicationValue),
 3661        write_update_attribute(QueryId, TableAlias, AttributeName, ApplicationValue).
 3662
 3663:-multifile(cql_atomic_value_check_hook/1). 3664write_atomic_update_attribute @
 3665        query_table_alias(QueryId, Schema, TableName, TableAlias)
 3666        \
 3667        write_update_attribute(QueryId, TableAlias, AttributeName, ApplicationValue)
 3668        <=>
 3669        ( var(ApplicationValue)
 3670        ; atom(ApplicationValue)
 3671        ; integer(ApplicationValue)
 3672        ; rational(ApplicationValue)
 3673        ; cql_atomic_value_check_hook(ApplicationValue)
 3674        ; ApplicationValue == {null}
 3675        ; ApplicationValue == {timestamp}
 3676        ; ApplicationValue == {user_id}
 3677        ; ApplicationValue == {transaction_id}
 3678        )
 3679        |
 3680        ( dbms(Schema, 'Microsoft SQL Server') ->
 3681            write_sql(QueryId,
 3682                      compile,
 3683                      top,
 3684                      [TableAlias, '.', attribute_name(AttributeName), =, ?|T],
 3685                      T,
 3686                      [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, update_value, _)],
 3687                      [])
 3688        ; dbms(Schema, 'PostgreSQL') ->
 3689            write_sql(QueryId,
 3690                      compile,
 3691                      top,
 3692                      [attribute_name(AttributeName), =, ?|T],
 3693                      T,
 3694                      [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, update_value, _)],
 3695                      [])
 3696        ; dbms(Schema, 'SQLite') ->
 3697            write_sql(QueryId,
 3698                      compile,
 3699                      top,
 3700                      [attribute_name(AttributeName), =, ?|T],
 3701                      T,
 3702                      [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, update_value, _)],
 3703                      [])
 3704
 3705        ).
 3706
 3707write_evaluated_update_attribute @
 3708        query_table_alias(QueryId, Schema, TableName, TableAlias)
 3709        \
 3710        write_update_attribute(QueryId, TableAlias, AttributeName, Expression)
 3711        <=>
 3712        ( dbms(Schema, 'Microsoft SQL Server') ; dbms(Schema, 'PostgreSQL') )
 3713        |
 3714        ( dbms(Schema, 'Microsoft SQL Server') ->
 3715            write_sql(QueryId,
 3716                      compile,
 3717                      top,
 3718                      [TableAlias, '.', attribute_name(AttributeName), =|T],
 3719                      T,
 3720                      [odbc_parameter(Schema, TableName, AttributeName, {null}, evaluated_update_attribute, _)],
 3721                      [])
 3722        ; dbms(Schema, 'PostgreSQL') ->
 3723            write_sql(QueryId,
 3724                      compile,
 3725                      top,
 3726                      [attribute_name(AttributeName), =|T],
 3727                      T,
 3728                      [odbc_parameter(Schema, TableName, AttributeName, {null}, evaluated_update_attribute, _)],
 3729                      [])
 3730        ),
 3731        write_expression(QueryId, Schema, TableName, AttributeName, TableAlias, Expression).
 3732
 3733write_evaluated_update_attribute_sqlite @
 3734        query_table_alias(QueryId, Schema, TableName, TableAlias)
 3735        \
 3736        write_update_attribute(QueryId, TableAlias, AttributeName, Expression)
 3737        <=>
 3738        dbms(Schema, 'SQLite')
 3739        |
 3740        % SQLite does not support the above method. Instead of Expression, we must actually put the entire FROM/WHERE clause here in a subquery like
 3741        % attribute_name(AttributeName) = SELECT(Expression FROM .......)
 3742        write_sql(QueryId,
 3743                  compile,
 3744                  top,
 3745                  [attribute_name(AttributeName), =, '(SELECT '|T],
 3746                  T,
 3747                  [odbc_parameter(Schema, TableName, AttributeName, {null}, evaluated_update_attribute, _)],
 3748                  []),
 3749        write_expression(QueryId, Schema, TableName, AttributeName, TableAlias, Expression),
 3750        Tail = [' AND ', TableAlias, '.rowid = ', TableName, '.rowid)'|T3],
 3751        write_sql(QueryId,
 3752                    compile,
 3753                    top,
 3754                    X,
 3755                    T3,
 3756                    Parameters,
 3757                    []),
 3758        find_copy_of_from(QueryId, X, Tail, Parameters).
 3759
 3760
 3761write_evaluated_update_binary_expression @
 3762        write_expression(QueryId, Schema, TableName, AttributeName, TableAlias, Expression)
 3763        <=>
 3764        nonvar(Expression),
 3765        functor(Expression, Operator, 2),
 3766        memberchk(Operator, [+, -, *, /])
 3767        |
 3768        arg(1, Expression, Lhs),
 3769        arg(2, Expression, Rhs),
 3770        ( dbms(Schema, 'SQLite') ->
 3771            % SQLite defaults to integer arithmetic. Fix this here
 3772            write_sql(QueryId, compile, top, ['(1.0*'|T1], T1, [], [])
 3773        ; otherwise->
 3774            write_sql(QueryId, compile, top, ['('|T1], T1, [], [])
 3775        ),
 3776        write_expression(QueryId, Schema, TableName, AttributeName, TableAlias, Lhs),
 3777        write_sql(QueryId, compile, top, [' ', Operator, ' '|T2], T2, [], []),
 3778        write_expression(QueryId, Schema, TableName, AttributeName, TableAlias, Rhs),
 3779        ( dbms(Schema, 'SQLite') ->
 3780            % SQLite defaults to integer arithmetic.
 3781            write_sql(QueryId, compile, top, ['*1.0)'|T3], T3, [], [])
 3782        ; otherwise->
 3783            write_sql(QueryId, compile, top, [')'|T3], T3, [], [])
 3784        ).
 3785
 3786write_evaluated_update_expression_attribute @
 3787        select_attribute(QueryId, select_attribute(_, _, _, TableAlias, AttributeName), 1, SelectAttributeVariableUsed, Variable)
 3788        \
 3789        write_expression(QueryId, _, _, _, _, Variable)
 3790        <=>
 3791        SelectAttributeVariableUsed = select_attribute_variable_used,
 3792        write_sql(QueryId, compile, top, [TableAlias, '.', attribute_name(AttributeName)|T], T, [], []).
 3793
 3794write_evaluated_update_expression_constant @
 3795        write_expression(QueryId, _, _, _, _, Constant)
 3796        <=>
 3797        integer(Constant)
 3798        |
 3799        atom_number(ConstantAtom, Constant),
 3800        write_sql(QueryId, compile, top, [ConstantAtom|T], T, [], []).
 3801
 3802write_evaluated_update_expression_parameter @
 3803        write_expression(QueryId, Schema, TableName, AttributeName, _, Variable)
 3804        <=>
 3805        var(Variable)
 3806        |
 3807        write_sql(QueryId,
 3808                  compile,
 3809                  top,
 3810                  [?|T],
 3811                  T,
 3812                  [odbc_parameter(Schema, TableName, AttributeName, Variable, evaluated_update_parameter, _)],
 3813                  []).
 3814
 3815
 3816write_evaluated_update_table_expression_attribute @
 3817        write_expression(QueryId, _, _, _, TableAlias, AttributeName)
 3818        <=>
 3819        write_sql(QueryId, compile, top, [TableAlias, '.', attribute_name(AttributeName)|T], T, [], []).
 3820
 3821
 3822write_delete_with_no_where_clause @
 3823        restriction_tree(QueryId, where, true)
 3824        \
 3825        phase(QueryId, initial),
 3826        delete_row(QueryId, TableName, _)
 3827        <=>
 3828        write_sql(QueryId, compile, top, ['DELETE'|T1], T1, [], []),
 3829        write_sql(QueryId, compile, join, [' FROM ', table_name(TableName)|T2], T2, [], []),
 3830        phase(QueryId, where).
 3831
 3832
 3833write_delete_with_where_clause @
 3834        phase(QueryId, initial),
 3835        delete_row(QueryId, TableName, TableAlias)
 3836        <=>
 3837        TableAlias = TableName,
 3838        write_sql(QueryId, compile, top, ['DELETE'|T1], T1, [], []),
 3839        write_sql(QueryId, compile, join, [' FROM ', TableAlias|T2], T2, [], []),
 3840        phase(QueryId, where).
 3841
 3842
 3843write_select_keyword @
 3844        phase(QueryId, initial)
 3845        <=>
 3846        write_sql(QueryId, compile, top, ['SELECT '|T], T, [], []),
 3847        phase(QueryId, distinct).
 3848
 3849
 3850write_select_distinct @
 3851        select_distinction(QueryId, DistinctionType)
 3852        \
 3853        phase(QueryId, distinct)
 3854        <=>
 3855        DistinctionType \== no_distinction
 3856        |
 3857        write_sql(QueryId, compile, top, ['DISTINCT '|T], T, [], []),
 3858        phase(QueryId, top).
 3859
 3860
 3861no_distinct @
 3862        phase(QueryId, distinct)
 3863        <=>
 3864        phase(QueryId, top).
 3865
 3866
 3867should_not_be_any_distinct_constraints_left_over @
 3868        check_for_orphan_distincts,
 3869        distinct(_, Distinct),
 3870        original_cql(Cql)
 3871        <=>
 3872        throw(format('Unused DISTINCT ~w in CQL: ~w', [Distinct, Cql])).
 3873
 3874select_variable_is_used_if_its_a_where_variable @
 3875        select_attribute(_, _, 1, SelectAttributeVariableUsed, Variable),
 3876        where_restriction_variable(Variable)
 3877        ==>
 3878        SelectAttributeVariableUsed = select_attribute_variable_used.
 3879
 3880select_variable_is_used_if_its_a_join_variable @
 3881        select_attribute(_, _, 1, SelectAttributeVariableUsed, Variable),
 3882        join_variable(Variable)
 3883        ==>
 3884        SelectAttributeVariableUsed = select_attribute_variable_used.
 3885
 3886
 3887select_variable_is_used_if_its_a_sub_query_join_variable @
 3888        select_attribute(_, _, 1, SelectAttributeVariableUsed, Variable),
 3889        sub_query_join_variable(Variable)
 3890        ==>
 3891        SelectAttributeVariableUsed = select_attribute_variable_used.
 3892
 3893check_for_orphan_select_variables_in_updates @
 3894        check_for_orphan_select_variables_in_updates,
 3895        query_type(QueryId, update),
 3896        select_attribute(QueryId, _, 1, SelectAttributeVariableUsed, Variable),
 3897        original_cql(Cql)
 3898        <=>
 3899        var(SelectAttributeVariableUsed)
 3900        |
 3901        throw(format('Unused SELECT variable ~w in UPDATE in CQL: ~w', [Variable, Cql])).
 3902
 3903original_cql_uniqueness @
 3904        original_cql(Cql)
 3905        \
 3906        original_cql(Cql)
 3907        <=>
 3908        true.
 3909
 3910
 3911statement_location_uniqueness @
 3912        cql_statement_location(FileName, LineNumber)
 3913        \
 3914        cql_statement_location(FileName, LineNumber)
 3915        <=>
 3916        true.
 3917
 3918
 3919top_n_error @
 3920        top(_, _, N),
 3921        original_cql(Cql)
 3922        ==>
 3923        \+ var(N),
 3924        \+ (integer(N), N >= 0)
 3925        |
 3926        throw(format('The N in top(N) must be an integer and not less than zero but found ~w in CQL: ~w', [N, Cql])).
 3927
 3928
 3929write_select_top_n @
 3930        phase(QueryId, top),
 3931        top(QueryId, Schema, N)
 3932        <=>
 3933        ( dbms(Schema, 'Microsoft SQL Server') ->
 3934            ( var(N) ->
 3935                write_sql(QueryId,
 3936                          compile,
 3937                          top,
 3938                          ['TOP (?) '|T],
 3939                          T,
 3940                          [odbc_explicit_type_parameter(integer, N, top_value)],
 3941                          [])
 3942            ; otherwise->
 3943                write_sql(QueryId, compile, top, ['TOP ', N, ' '|T], T, [], [])
 3944            )
 3945        ; dbms(Schema, 'PostgreSQL') ->
 3946            limit(QueryId, Schema, N)
 3947        ; dbms(Schema, 'SQLite') ->
 3948            limit(QueryId, Schema, N)
 3949        ),
 3950        phase(QueryId, select_attributes).
 3951
 3952
 3953no_top @
 3954        phase(QueryId, top)
 3955        <=>
 3956        phase(QueryId, select_attributes).
 3957
 3958
 3959write_limit @
 3960        write_limit,
 3961        limit(QueryId, Schema, N)
 3962        <=>
 3963        ( ( dbms(Schema, 'PostgreSQL') ; dbms(Schema, 'SQLite') )->
 3964            (var(N)->
 3965               write_sql(QueryId,
 3966                         compile,
 3967                          where,
 3968                         [' LIMIT (?) '|T],
 3969                         T,
 3970                         [odbc_explicit_type_parameter(integer, N, top_value)],
 3971                         [])
 3972            ; otherwise->
 3973                write_sql(QueryId, compile, where, [' LIMIT ', N, ' '|T], T, [], [])
 3974            )
 3975        ; otherwise->
 3976           true).
 3977
 3978no_limit @
 3979        write_limit
 3980        <=>
 3981        true.
 3982
 3983write_sub_query_select @
 3984        sub_query_select(QueryId)
 3985        \
 3986        phase(QueryId, select_attributes)
 3987        <=>
 3988        write_sql(QueryId, compile, top, [*|T], T, [], []),
 3989        phase(QueryId, from).
 3990
 3991
 3992write_select_for_insert_attributes @
 3993        phase(QueryId, select_attributes),
 3994        query_table_alias(QueryId, _, _, _)
 3995        \
 3996        select_for_insert_variables([Variable|InsertVariables], InsertTableName)
 3997        <=>
 3998        select_for_insert_variable(QueryId, Variable, InsertTableName),
 3999        select_for_insert_variables(InsertVariables, InsertTableName).
 4000
 4001
 4002write_select_for_insert_attributes_complete @
 4003        phase(QueryId, select_attributes),
 4004        select_for_insert_variables([], _)
 4005        <=>
 4006        phase(QueryId, from).
 4007
 4008
 4009write_select_for_insert_count @
 4010        select_for_insert_variable(QueryId, Variable, _),
 4011        select_attribute(QueryId, select_attribute(aggregation(count), _, _, TableAlias, AttributeName), 1, _, Variable)
 4012        <=>
 4013        write_select_attribute(QueryId,
 4014                               compile,
 4015                               ['count(', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 4016                               T,
 4017                               ignore_output).
 4018
 4019
 4020write_select_for_insert_aggregation @
 4021        select_for_insert_variable(QueryId, Variable, _),
 4022        select_attribute(QueryId, select_attribute(aggregation(AggregationOperator), _, _, TableAlias, AttributeName), 1, _, Variable)
 4023        <=>
 4024        % Why did someone try and do this?!
 4025        %map_database_atom(AggregationOperator, AggregationOperatorUc),
 4026        write_select_attribute(QueryId,
 4027                               compile,
 4028                               [AggregationOperator, '(', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 4029                               T,
 4030                               ignore_output).
 4031
 4032
 4033write_select_for_insert_select_constant @
 4034        select_for_insert_variable(QueryId, Variable, InsertTableName),
 4035        select_attribute(QueryId, select_attribute(plain, Schema, _, _, AttributeName), 1, _, selection_constant(Variable))
 4036        <=>
 4037        write_select_attribute(QueryId,
 4038                               compile,
 4039                               ['? AS ', attribute_name(AttributeName)|T],
 4040                               T,
 4041                               selection_constant(Schema, InsertTableName, AttributeName, Variable)).
 4042
 4043
 4044write_select_for_insert_plain_attribute @
 4045        select_for_insert_variable(QueryId, Variable, _),
 4046        select_attribute(QueryId, select_attribute(plain, _, _, TableAlias, AttributeName), 1, _, Variable)
 4047        <=>
 4048        write_select_attribute(QueryId,
 4049                               compile,
 4050                               [TableAlias, '.', attribute_name(AttributeName)|T],
 4051                               T,
 4052                               ignore_output).
 4053
 4054
 4055write_select_attributes @
 4056        select_attribute(QueryId, _, _, _, _)
 4057        \
 4058        phase(QueryId, select_attributes)
 4059        <=>
 4060        write_select_attributes(QueryId),
 4061        phase(QueryId, from).
 4062
 4063
 4064write_do_nothing_select @
 4065        phase(QueryId, select_attributes)
 4066        <=>
 4067        write_sql(QueryId, compile, top, [0|T], T, [], [ignore_output]),
 4068        % no human
 4069        phase(QueryId, from).
 4070
 4071
 4072write_select_count_attribute @
 4073        write_select_attributes(QueryId),
 4074        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4075        \
 4076        select_attribute(QueryId, select_attribute(aggregation(count), Schema, _, TableAlias, AttributeName), 1, _, Variable)
 4077        <=>
 4078        get_data_size(Schema, TableName, AttributeName, Size),
 4079        include_select_attribute(QueryId,
 4080                                 compile,
 4081                                 Size,
 4082                                 ['count(', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 4083                                 T,
 4084                                 count(Variable)).
 4085
 4086write_select_avg_attribute_for_postgres @
 4087        write_select_attributes(QueryId),
 4088        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4089        \
 4090        select_attribute(QueryId, select_attribute(aggregation(avg), Schema, _, TableAlias, AttributeName), 1, _, Variable)
 4091        <=>
 4092        dbms(Schema, 'PostgreSQL')
 4093        |
 4094        %map_database_atom(avg, AggregationOperatorUc),
 4095        upcase_atom(avg, AggregationOperatorUc),
 4096        get_data_size(Schema, TableName, AttributeName, Size),
 4097        include_select_attribute(QueryId,
 4098                                 compile,
 4099                                 Size,
 4100                                 [AggregationOperatorUc, '(', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 4101                                 T,
 4102                                 avg(Variable)).
 4103
 4104write_select_aggregation_attribute @
 4105        write_select_attributes(QueryId),
 4106        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4107        \
 4108        select_attribute(QueryId, select_attribute(aggregation(AggregationOperator), Schema, _, TableAlias, AttributeName), 1, _, Variable)
 4109        <=>
 4110        get_data_size(Schema, TableName, AttributeName, Size),
 4111        %map_database_atom(AggregationOperator, AggregationOperatorUc),
 4112        upcase_atom(AggregationOperator, AggregationOperatorUc),
 4113        include_select_attribute(QueryId,
 4114                                 compile,
 4115                                 Size,
 4116                                 [AggregationOperatorUc, '(', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 4117                                 T,
 4118                                 output(Schema, TableName, AttributeName, Variable)).
 4119
 4120
 4121write_top_level_select_attribute @
 4122        write_select_attributes(QueryId),
 4123        query(QueryId, _, top_level_query),
 4124        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4125        \
 4126        select_attribute(QueryId, select_attribute(plain, Schema, _, TableAlias, AttributeName), 1, _, Variable)
 4127        <=>
 4128        get_data_size(Schema, TableName, AttributeName, Size),
 4129        include_select_attribute(QueryId,
 4130                                 if_var(Variable),
 4131                                 Size,
 4132                                 [TableAlias, '.', attribute_name(AttributeName)|T],
 4133                                 T,
 4134                                 output(Schema, TableName, AttributeName, Variable)).
 4135
 4136
 4137
 4138flush_select_attributes @
 4139        write_select_attributes(QueryId)
 4140        ==>
 4141        collect_select_attributes(QueryId, Unsorted),
 4142        keysort(Unsorted, SortedWithKeys),
 4143        cql_strip_sort_keys(SortedWithKeys, Sorted),
 4144        actually_write_select_attributes(QueryId, compile, Sorted).
 4145
 4146collect_select_attributes @
 4147        collect_select_attributes(QueryId, Tail),
 4148        include_select_attribute(QueryId, CompileInstruction, Size, Tokens, TokenTail, Attribute)
 4149        <=>
 4150        Tail = [Size-select_info(CompileInstruction, Tokens, TokenTail, Attribute)|NewTail],
 4151        collect_select_attributes(QueryId, NewTail).
 4152
 4153finished_collecting_select_attributes @
 4154        collect_select_attributes(_, Tail)
 4155        <=>
 4156        Tail = [].
 4157
 4158actually_write_select_attributes(_, _, []).
 4159actually_write_select_attributes(QueryId, _PreviousCompileInstruction, [select_info(CompileInstruction, Tokens, Tail, Attribute)|More]):-
 4160        %instruction_conjunction(PreviousCompileInstruction, CompileInstruction, Conjunction),
 4161        write_select_attribute(QueryId, CompileInstruction, Tokens, Tail, Attribute),
 4162        actually_write_select_attributes(QueryId, CompileInstruction, More).
 4163
 4164
 4165
 4166write_select_attribute_with_leading_comma @
 4167        select_attribute_written(QueryId)
 4168        \
 4169        write_select_attribute(QueryId, CompileInstruction, SqlTokens, Tail, Output)
 4170        <=>
 4171        write_sql(QueryId, CompileInstruction, top, [', '|T], T, [], []),
 4172        write_select_attribute_1(QueryId, CompileInstruction, SqlTokens, Tail, Output).
 4173
 4174
 4175write_select_attribute_without_leading_comma @
 4176        write_select_attribute(QueryId, _CompileInstruction, SqlTokens, Tail, Output)
 4177        <=>
 4178        write_select_attribute_1(QueryId, compile, SqlTokens, Tail, Output),
 4179        select_attribute_written(QueryId).
 4180
 4181
 4182write_select_attribute_1a @
 4183        write_select_attribute_1(QueryId, CompileInstruction, SqlTokens, Tail, selection_constant(Schema, TableName, AttributeName, ApplicationValue))
 4184        <=>
 4185        write_sql(QueryId,
 4186                  CompileInstruction,
 4187                  top,
 4188                  SqlTokens,
 4189                  Tail,
 4190                  [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, insert_value, _)],
 4191                  [ignore_output]).
 4192
 4193write_select_attribute_1c @
 4194        write_select_attribute_1(QueryId, CompileInstruction, SqlTokens, Tail, Output)
 4195        <=>
 4196        write_sql(QueryId, CompileInstruction, top, SqlTokens, Tail, [], [Output]).
 4197
 4198in_line_join_on @
 4199        create_in_line_joins,
 4200        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4201        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4202        ==>
 4203        dbms(Schema, 'Microsoft SQL Server'),
 4204        var(JoinVariableA),
 4205        JoinVariableA == JoinVariableB,
 4206        TableAliasA \== TableAliasB
 4207        |
 4208        join_variable(JoinVariableA),
 4209        join_variable(JoinVariableB),
 4210        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4211
 4212
 4213in_line_join_on @
 4214        create_in_line_joins,
 4215        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4216        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4217        ==>
 4218        dbms(Schema, 'SQLite'),
 4219        var(JoinVariableA),
 4220        JoinVariableA == JoinVariableB,
 4221        TableAliasA \== TableAliasB
 4222        |
 4223        join_variable(JoinVariableA),
 4224        join_variable(JoinVariableB),
 4225        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4226
 4227
 4228/* We can end up with selects mixed in with other types because of how
 4229   translate_select ends up getting called to parse the where clauses of
 4230   other types of query. In this case, we can simply delete all the selects.
 4231*/
 4232
 4233a_query_cannot_be_select_and_something_else @
 4234        query_type(QueryId, _)
 4235        \
 4236        query_type(QueryId, select)
 4237        <=>
 4238        true.
 4239
 4240
 4241in_line_join_on_postgres_select_insert_or_delete @
 4242        create_in_line_joins,
 4243        query_type(QueryId, QueryType),
 4244        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4245        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4246        ==>
 4247        dbms(Schema, 'PostgreSQL'),
 4248        memberchk(QueryType, [select, insert, delete]),
 4249        var(JoinVariableA),
 4250        JoinVariableA == JoinVariableB,
 4251        TableAliasA \== TableAliasB
 4252        |
 4253        join_variable(JoinVariableA),
 4254        join_variable(JoinVariableB),
 4255        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4256
 4257in_line_join_on_postgres_update_but_not_target @
 4258        create_in_line_joins,
 4259        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4260        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB),
 4261        update_table_alias(QueryId, _, _, TargetAlias)
 4262        ==>
 4263        dbms(Schema, 'PostgreSQL'),
 4264        var(JoinVariableA),
 4265        JoinVariableA == JoinVariableB,
 4266        TableAliasA \== TableAliasB,
 4267        TableAliasA \== TargetAlias,
 4268        TableAliasB \== TargetAlias
 4269        |
 4270        join_variable(JoinVariableA),
 4271        join_variable(JoinVariableB),
 4272        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4273
 4274in_line_join_on_postgres_and_is_target @
 4275        create_in_line_joins,
 4276        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4277        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB),
 4278        update_table_alias(QueryId, _, _, TargetAlias)
 4279        ==>
 4280        dbms(Schema, 'PostgreSQL'),
 4281        var(JoinVariableA),
 4282        JoinVariableA == JoinVariableB,
 4283        TableAliasA \== TableAliasB,
 4284        ( TableAliasA == TargetAlias ; TableAliasB == TargetAlias)
 4285        |
 4286        join_variable(JoinVariableA),
 4287        join_variable(JoinVariableB),
 4288        comparison(QueryId, attribute(Schema, TableAliasA, AttributeNameA), ==, attribute(Schema, TableAliasB, AttributeNameB)),
 4289        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4290
 4291cleanup_create_in_line_joins @
 4292        create_in_line_joins
 4293        <=>
 4294        true.
 4295
 4296explicit_join_on_postgres_update @
 4297        create_join_points,
 4298        update_table_alias(QueryId, _, _, TargetAlias),
 4299        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4300        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4301        \
 4302        % Use up the comparison/4 as we don't want it in the WHERE clause
 4303        comparison(QueryId, JoinVariableA, ==, JoinVariableB)
 4304        <=>
 4305        dbms(Schema, 'PostgreSQL'),
 4306        var(JoinVariableA),
 4307        var(JoinVariableB),
 4308        TableAliasA \== TableAliasB, TableAliasA \== TargetAlias, TableAliasB \== TargetAlias
 4309        |
 4310        join_variable(JoinVariableA),
 4311        join_variable(JoinVariableB),
 4312        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4313
 4314explicit_join_on_postgres_other @
 4315        create_join_points,
 4316        query_type(QueryId, Type),
 4317        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4318        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4319        \
 4320        % Use up the comparison/4 as we don't want it in the WHERE clause
 4321        comparison(QueryId, JoinVariableA, ==, JoinVariableB)
 4322        <=>
 4323        dbms(Schema, 'PostgreSQL'),
 4324        memberchk(Type, [select, insert, delete]),
 4325        var(JoinVariableA),
 4326        var(JoinVariableB),
 4327        TableAliasA \== TableAliasB
 4328        |
 4329        join_variable(JoinVariableA),
 4330        join_variable(JoinVariableB),
 4331        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4332
 4333
 4334
 4335explicit_join_on @
 4336        create_join_points,
 4337        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4338        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4339        \
 4340        % Use up the comparison/4 as we don't want it in the WHERE clause
 4341        comparison(QueryId, JoinVariableA, ==, JoinVariableB)
 4342        <=>
 4343        dbms(Schema, 'Microsoft SQL Server'),
 4344        var(JoinVariableA),
 4345        var(JoinVariableB),
 4346        TableAliasA \== TableAliasB
 4347        |
 4348        join_variable(JoinVariableA),
 4349        join_variable(JoinVariableB),
 4350        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4351
 4352explicit_join_on @
 4353        create_join_points,
 4354        attribute_binding(QueryId, attribute(Schema, TableAliasA, AttributeNameA), JoinVariableA),
 4355        attribute_binding(QueryId, attribute(Schema, TableAliasB, AttributeNameB), JoinVariableB)
 4356        \
 4357        % Use up the comparison/4 as we don't want it in the WHERE clause
 4358        comparison(QueryId, JoinVariableA, ==, JoinVariableB)
 4359        <=>
 4360        dbms(Schema, 'SQLite'),
 4361        var(JoinVariableA),
 4362        var(JoinVariableB),
 4363        TableAliasA \== TableAliasB
 4364        |
 4365        join_variable(JoinVariableA),
 4366        join_variable(JoinVariableB),
 4367        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB).
 4368
 4369
 4370avoid_duplicate_join_ons @
 4371        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB)
 4372        \
 4373        join_on(TableAliasB, AttributeNameB, TableAliasA, AttributeNameA)
 4374        <=>
 4375        true.
 4376
 4377
 4378search_for_join_aliases_0 @
 4379        join(_, Join, LhsJoin, _, RhsJoin)
 4380        ==>
 4381        search_for_join_aliases(Join, lhs, LhsJoin),
 4382        search_for_join_aliases(Join, rhs, RhsJoin).
 4383
 4384
 4385search_for_join_aliases_1 @
 4386        join_leaf(Join, TableAlias),
 4387        search_for_join_aliases(JoinParent, Side, Join)
 4388        ==>
 4389        join_alias(JoinParent, Side, TableAlias).
 4390
 4391
 4392search_for_join_aliases_2 @
 4393        join(_, Join, LhsJoin, _, _),
 4394        search_for_join_aliases(JoinParent, Side, Join)
 4395        ==>
 4396        search_for_join_aliases(JoinParent, Side, LhsJoin).
 4397
 4398
 4399search_for_join_aliases_3 @
 4400        join(_, Join, _, _, RhsJoin),
 4401        search_for_join_aliases(JoinParent, Side, Join)
 4402        ==>
 4403        search_for_join_aliases(JoinParent, Side, RhsJoin).
 4404
 4405% This is for PostgreSQL
 4406% If we have an implicit join in some query QueryId, we get the join for free.
 4407% However, to do the pre-state-change stuff, we still have to build the join in memory
 4408% and capture the ON clause. This formula creates the two join points in SubQueryId
 4409% which is where the on/4 term goes and implicit_join_sql/3 looks.
 4410% Note that this is only used for explicit on clauses.
 4411search_for_join_aliases_4 @
 4412        implicit_join(QueryId, _, SubQueryId),
 4413        update_table_alias(QueryId, _Schema, _TableName, TableAlias)
 4414        ==>
 4415        join_alias(SubQueryId, lhs, TableAlias),
 4416        search_for_join_aliases(SubQueryId, rhs, QueryId).
 4417
 4418
 4419
 4420add_on_from_join_on @
 4421        resolve_join_points,
 4422        join_alias(Join, lhs, TableAliasLhs),
 4423        join_alias(Join, rhs, TableAliasRhs)
 4424        \
 4425        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB)
 4426        <=>
 4427        ( TableAliasLhs == TableAliasA,
 4428          TableAliasRhs == TableAliasB
 4429        ; TableAliasLhs == TableAliasB,
 4430          TableAliasRhs == TableAliasA
 4431        )
 4432        |
 4433        add_on(Join, TableAliasA-AttributeNameA==TableAliasB-AttributeNameB).
 4434
 4435
 4436add_ons @
 4437        on(Join, Resolved, On),
 4438        add_on(Join, ExistingOn)
 4439        <=>
 4440        on(Join, Resolved, (ExistingOn, On)).
 4441
 4442
 4443add_on @
 4444        add_on(Join, ExistingOn)
 4445        <=>
 4446        on(Join, _, ExistingOn).
 4447
 4448
 4449resolve_join_points @
 4450        resolve_join_points
 4451        \
 4452        on(Join, Resolved, On)
 4453        <=>
 4454        var(Resolved)
 4455        |
 4456        resolve_join_points(Join, On, NewOn),
 4457        on(Join, resolved, NewOn).
 4458
 4459
 4460cleanup_resolve_join_points @
 4461        resolve_join_points
 4462        <=>
 4463        true.
 4464
 4465
 4466resolve_join_points_1 @
 4467        resolve_join_points(Join, (Lhs, Rhs), NewOn)
 4468        <=>
 4469        resolve_join_points(Join, Lhs, NewLhs),
 4470        resolve_join_points(Join, Rhs, NewRhs),
 4471        NewOn = (NewLhs, NewRhs).
 4472
 4473
 4474resolve_join_points_2 @
 4475        resolve_join_points(Join, (Lhs ; Rhs), NewOn)
 4476        <=>
 4477        resolve_join_points(Join, Lhs, NewLhs),
 4478        resolve_join_points(Join, Rhs, NewRhs),
 4479        NewOn = (NewLhs ; NewRhs).
 4480
 4481
 4482resolve_join_points_3 @
 4483        % Ihese come from in-line (shared varoabel) joins and explicit where-style restrictions
 4484        resolve_join_points(_, TableAliasLhs-AttributeNameLhs==TableAliasRhs-AttributeNameRhs, NewOn)
 4485        <=>
 4486        NewOn = (TableAliasLhs-AttributeNameLhs==TableAliasRhs-AttributeNameRhs).
 4487
 4488
 4489resolve_join_points_4 @
 4490        % These come from on clauses
 4491        attribute_binding(QueryId, attribute(Schema, TableAliasLhs, AttributeNameLhs), JoinVariableA),
 4492        attribute_binding(QueryId, attribute(Schema, TableAliasRhs, AttributeNameRhs), JoinVariableB),
 4493        join_alias(Join, lhs, TableAliasLhs),
 4494        join_alias(Join, rhs, TableAliasRhs)
 4495        \
 4496        resolve_join_points(Join, A==B, NewOn)
 4497        <=>
 4498        var(A),
 4499        var(B),
 4500        ( (A==B) == (JoinVariableA==JoinVariableB)
 4501        ; (B==A) == (JoinVariableA==JoinVariableB)
 4502        )
 4503        |
 4504        not_a_singleton(JoinVariableA),
 4505        not_a_singleton(JoinVariableB),
 4506        join_variable(JoinVariableA),
 4507        join_variable(JoinVariableB),
 4508        NewOn = (TableAliasLhs-AttributeNameLhs==TableAliasRhs-AttributeNameRhs).
 4509
 4510
 4511resolve_join_points_5 @
 4512        attribute_binding(_, attribute(_, TableAlias, _), JoinVariable),
 4513        join_alias(Join, _, TableAlias)
 4514        \
 4515        resolve_join_points(Join, On, NewOn)
 4516        <=>
 4517        On =.. [Operator, V, Rhs],
 4518        JoinVariable == V
 4519        |
 4520        not_a_singleton(JoinVariable),
 4521        join_variable(JoinVariable),
 4522        NewOn =.. [Operator, TableAlias-JoinVariable, Rhs].
 4523
 4524
 4525resolve_join_points_6 @
 4526        attribute_binding(_, attribute(_, TableAlias, _), JoinVariable),
 4527        join_alias(Join, _, TableAlias)
 4528        \
 4529        resolve_join_points(Join, On, NewOn)
 4530        <=>
 4531        On =.. [Operator, Lhs, V],
 4532        JoinVariable == V
 4533        |
 4534        not_a_singleton(JoinVariable),
 4535        join_variable(JoinVariable),
 4536        NewOn =.. [Operator, Lhs, TableAlias-JoinVariable].
 4537
 4538
 4539resolve_join_points_7 @
 4540        resolve_join_points(_, On, _)
 4541        <=>
 4542        throw(format('Cannot translate ON specification: ~w', [On])).
 4543
 4544
 4545join_variable_must_be_a_variable @
 4546        join_variable(Variable)
 4547        <=>
 4548        nonvar(Variable)
 4549        |
 4550        true.
 4551
 4552
 4553join_variable_is_unique @
 4554        join_variable(Variable)
 4555        \
 4556        join_variable(Variable)
 4557        <=>
 4558        true.
 4559
 4560
 4561update_not_from_source @
 4562        query_table_alias(QueryId, _, _, TableAlias),
 4563        update_table_alias(QueryId, Schema, _, TargetAlias)
 4564        \
 4565        phase(QueryId, Phase)
 4566        <=>
 4567        dbms(Schema, 'PostgreSQL'),
 4568        Phase == from,
 4569        TableAlias \== TargetAlias
 4570        |
 4571        write_sql(QueryId, compile, top, [' FROM '|T], T, [], []),
 4572        write_join(QueryId, QueryId),
 4573        phase(QueryId, where).
 4574
 4575update_from_source @
 4576        query_table_alias(QueryId, _, _, _),
 4577        update_table_alias(QueryId, Schema, _, _)
 4578        \
 4579        phase(QueryId, from)
 4580        <=>
 4581        dbms(Schema, 'PostgreSQL')
 4582        |
 4583        phase(QueryId, where).
 4584
 4585
 4586select_from @
 4587        query_table_alias(QueryId, _, _, _)
 4588        \
 4589        phase(QueryId, from)
 4590        <=>
 4591        write_sql(QueryId, compile, join, [' FROM '|T], T, [], []),
 4592        write_join(QueryId, QueryId),
 4593        phase(QueryId, where).
 4594
 4595
 4596no_from_statement @
 4597        phase(QueryId, from)
 4598        <=>
 4599        phase(QueryId, where).
 4600
 4601
 4602% The inclusion of the target alias is implied in Postgres UPDATE ... FROM
 4603write_join_leaf_unless_target @
 4604        join_leaf(Join, TableAlias),
 4605        query_table_alias(QueryId, _, TableName, TableAlias),
 4606        update_table_alias(QueryId, Schema, _, TargetAlias)
 4607        \
 4608        write_join(QueryId, Join)
 4609        <=>
 4610        dbms(Schema, 'PostgreSQL'),
 4611        TargetAlias \== TableAlias
 4612        |
 4613        write_sql(QueryId, compile, join, [table_name(TableName), ' ', TableAlias|T], T, [], []).
 4614
 4615write_join_leaf @
 4616        join_leaf(Join, TableAlias),
 4617        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4618        \
 4619        write_join(QueryId, Join)
 4620        <=>
 4621        write_sql(QueryId, compile, join, [table_name(TableName), ' ', TableAlias|T], T, [], []),
 4622        write_lock_hint(QueryId, Schema, TableAlias).
 4623
 4624
 4625write_lock_hint @
 4626        write_lock_hint(QueryId, Schema, TableAlias),
 4627        nolock(QueryId, TableAlias)
 4628        <=>
 4629        dbms(Schema, 'Microsoft SQL Server')
 4630        |
 4631        write_sql(QueryId, compile, join, [' WITH (NOLOCK)'|T], T, [], []).
 4632
 4633% Ignored for PostgreSQL and SQLite
 4634cleanup_write_lock_hint @
 4635        write_lock_hint(_, _, _)
 4636        <=>
 4637        true.
 4638
 4639
 4640
 4641write_join_clause @
 4642        query(QueryId, Schema, _)
 4643        \
 4644        join(QueryId, Join, LhsJoin, JoinType, RhsJoin),
 4645        write_join(QueryId, Join),
 4646        on(Join, _, On)
 4647        <=>
 4648        write_sql(QueryId, compile, join, ['('|T1], T1, [], []),
 4649        write_join(QueryId, LhsJoin),
 4650        write_sql(QueryId, compile, join, [' ', JoinType, ' '|T2], T2, [], []),
 4651        write_join(QueryId, RhsJoin),
 4652        write_sql(QueryId, compile, join, [' ON '|T3], T3, [], []),
 4653        write_join_ons(QueryId, On),
 4654        write_sql(QueryId, compile, join, [')'|T4], T4, [], []),
 4655
 4656        ( debugging(index_suggestions) ->
 4657            on_to_where(Schema, On, RestrictionTree),
 4658            cql_suggest_indices(RestrictionTree, QueryId)
 4659
 4660        ; otherwise ->
 4661            true
 4662        ).
 4663
 4664
 4665write_join_on_conjunction @
 4666        write_join_ons(QueryId, (Lhs, Rhs))
 4667        <=>
 4668        write_join_ons(QueryId, Lhs),
 4669        write_sql(QueryId, compile, join, [' AND '|T], T, [], []),
 4670        write_join_ons(QueryId, Rhs).
 4671
 4672
 4673write_join_on_disjunction @
 4674        write_join_ons(QueryId, (Lhs ; Rhs))
 4675        <=>
 4676        write_sql(QueryId, compile, join, ['('|T1], T1, [], []),
 4677        write_join_ons(QueryId, Lhs),
 4678        write_sql(QueryId, compile, join, [' OR '|T2], T2, [], []),
 4679        write_join_ons(QueryId, Rhs),
 4680        write_sql(QueryId, compile, join, [')'|T3], T3, [], []).
 4681
 4682
 4683write_join_on_attributes @
 4684        write_join_ons(QueryId, TableAliasLhs-AttributeNameLhs==TableAliasRhs-AttributeNameRhs)
 4685        <=>
 4686        write_sql(QueryId,
 4687                  compile,
 4688                  join,
 4689                  [TableAliasLhs, '.', attribute_name(AttributeNameLhs), =, TableAliasRhs, '.', attribute_name(AttributeNameRhs)|T],
 4690                  T,
 4691                  [],
 4692                  []).
 4693
 4694write_join_on_lhs @
 4695        attribute_binding(_, attribute(Schema, TableAlias, AttributeName), Variable)
 4696        \
 4697        write_join_ons(QueryId, On)
 4698        <=>
 4699        var(Variable),
 4700        On =.. [ComparisonOperator, ApplicationValue, Rhs],
 4701        error_on_comparison_operator(Schema, ComparisonOperator),
 4702        Rhs == TableAlias-Variable
 4703        |
 4704        write_restriction(QueryId, compile, join, ApplicationValue, ComparisonOperator, attribute(Schema, TableAlias, AttributeName)).
 4705
 4706
 4707write_join_on_rhs @
 4708        attribute_binding(_, attribute(Schema, TableAlias, AttributeName), Variable)
 4709        \
 4710        write_join_ons(QueryId, On)
 4711        <=>
 4712        var(Variable),
 4713        On =.. [ComparisonOperator, Lhs, ApplicationValue],
 4714        error_on_comparison_operator(Schema, ComparisonOperator),
 4715        Lhs == TableAlias-Variable
 4716        |
 4717        write_restriction(QueryId, compile, join, attribute(Schema, TableAlias, AttributeName), ComparisonOperator, ApplicationValue).
 4718
 4719error_on_comparison_operator(Schema, ComparisonOperator) :-
 4720        ( ground(ComparisonOperator),
 4721          prolog_to_sql_comparison_operator(Schema, ComparisonOperator, _, _) ->
 4722            true
 4723        ;
 4724            throw(format('Invalid comparison operator in JOIN ON: ~w', [ComparisonOperator]))
 4725        ).
 4726
 4727query_table_alias_no_duplicates @
 4728        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4729        \
 4730        query_table_alias(QueryId, Schema, TableName, TableAlias)
 4731        <=>
 4732        true.
 4733
 4734
 4735check_update_where_restriction @
 4736        phase(QueryId, where),
 4737        restriction_tree(QueryId, where, true),
 4738        state_change_query(QueryId, StateChangeType, _, _)
 4739        ==>
 4740        ( StateChangeType == delete
 4741        ; StateChangeType == update
 4742        )
 4743        |
 4744        no_where_restriction(StateChangeType).
 4745
 4746
 4747no_where_restriction_permitted @
 4748        no_where_restriction(_),
 4749        absence_of_where_restriction_is_deliberate
 4750        <=>
 4751        true.
 4752
 4753
 4754deletes_and_updates_must_have_a_where_restriction @
 4755        no_where_restriction(StateChangeType)
 4756        <=>
 4757        upcase_atom(StateChangeType, StateChangeTypeUc),
 4758        throw(format('~w has no WHERE restriction - check RESTRICTION variables declared', [StateChangeTypeUc])).
 4759
 4760
 4761remove_empty_restriction_tree @
 4762        phase(QueryId, where)
 4763        \
 4764        restriction_tree(QueryId, where, true)
 4765        <=>
 4766        true.
 4767
 4768
 4769where_restriction_clause @
 4770        phase(QueryId, where),
 4771        restriction_tree(QueryId, where, RestrictionTree)
 4772        <=>
 4773        collect_indices(QueryId),
 4774        write_sql(QueryId, compile, where, [' WHERE '|T], T, [], []),
 4775        write_restriction_tree(QueryId, where, RestrictionTree),
 4776        phase(QueryId, group_by).
 4777
 4778sqlite_must_have_where @
 4779        % This is because we add to the WHERE clause programmatically to compute subqueries for update expressions
 4780        query(QueryId, Schema, _)
 4781        \
 4782        phase(QueryId, where)
 4783        <=>
 4784        dbms(Schema, 'SQLite')
 4785        |
 4786        write_sql(QueryId, compile, where, [' WHERE 1=1 '|T], T, [], []),
 4787        phase(QueryId, group_by).
 4788
 4789
 4790no_where_restriction_clause @
 4791        phase(QueryId, where)
 4792        <=>
 4793        phase(QueryId, group_by).
 4794
 4795
 4796having_restriction_clause @
 4797        phase(QueryId, having),
 4798        restriction_tree(QueryId, having, RestrictionTree)
 4799        <=>
 4800        write_sql(QueryId, compile, having, [' HAVING '|T], T, [], []),
 4801        write_restriction_tree(QueryId, having, RestrictionTree),
 4802        phase(QueryId, order_by).
 4803
 4804
 4805no_having_restriction_clause @
 4806        phase(QueryId, having)
 4807        <=>
 4808        phase(QueryId, order_by).
 4809
 4810suggest_indices @
 4811        write_restriction_tree(QueryId, _, RestrictionTree)
 4812        \
 4813        collect_indices(QueryId)
 4814        <=>
 4815        ( debugging(index_suggestions) ->
 4816            cql_suggest_indices(RestrictionTree, QueryId)
 4817
 4818        ; otherwise ->
 4819            true
 4820        ).
 4821
 4822write_restriction_clause @
 4823        write_restriction_tree(QueryId, RestrictionType, RestrictionTree)
 4824        <=>
 4825        ( RestrictionTree = or(Lhs, Rhs) ->
 4826            Operator = 'OR'
 4827
 4828        ; RestrictionTree = and(Lhs, Rhs) ->
 4829            Operator = 'AND'
 4830        )
 4831        |
 4832        write_sql(QueryId, compile, where, ['('|T1], T1, [], []),
 4833        write_restriction_tree(QueryId, RestrictionType, Lhs),
 4834        write_sql(QueryId, compile, where, [' ', Operator, ' '|T2], T2, [], []),
 4835        write_restriction_tree(QueryId, RestrictionType, Rhs),
 4836        write_sql(QueryId, compile, where, [')'|T3], T3, [], []).
 4837
 4838write_restriction_leaf_for_ignore_if_null_on_rhs @
 4839        query_table_alias(_, Schema, _TableName, TableAlias)
 4840        \
 4841        write_restriction_tree(QueryId, RestrictionType, comparison(attribute(Schema, TableAlias, AttributeName), Operator, ignore_if_null(Variable)))
 4842        <=>
 4843        write_restriction(QueryId, if_not_null(Variable), RestrictionType, attribute(Schema, TableAlias, AttributeName), Operator, Variable),
 4844        write_sql(QueryId, if_null(Variable), RestrictionType, ['1 = 1'|T], T, [], []).
 4845
 4846
 4847write_restriction_leaf_for_ignore_if_null_on_lhs @
 4848        query_table_alias(_, Schema, _TableName, TableAlias)
 4849        \
 4850        write_restriction_tree(QueryId, RestrictionType, comparison(ignore_if_null(Variable), Operator, attribute(Schema, TableAlias, AttributeName)))
 4851        <=>
 4852        write_restriction(QueryId, if_not_null(Variable), RestrictionType, Variable, Operator, attribute(Schema, TableAlias, AttributeName)),
 4853        write_sql(QueryId, if_null(Variable), RestrictionType, ['1 = 1'|T], T, [], []).
 4854
 4855write_restriction_leaf_for_if_not_var_on_rhs @
 4856        write_restriction_tree(QueryId, RestrictionType, comparison(Attribute, ==, if_not_var(Variable)))
 4857        <=>
 4858        write_restriction(QueryId, if_not_var(Variable), RestrictionType, Attribute, ==, if_not_var(Variable)),
 4859        write_sql(QueryId, if_var(Variable), RestrictionType, ['1 = 1'|T], T, [], []).
 4860
 4861write_restriction_leaf @
 4862        write_restriction_tree(QueryId, RestrictionType, comparison(Lhs, Operator, Rhs))
 4863        <=>
 4864        write_restriction(QueryId, compile, RestrictionType, Lhs, Operator, Rhs).
 4865
 4866
 4867write_restriction_between_attribute_and_ignore_if_null @
 4868        query_table_alias(_, Schema, TableName, TableAlias)
 4869        \
 4870        write_restriction(QueryId,
 4871                          CompileInstruction,
 4872                          RestrictionType,
 4873                          attribute(Schema, TableAlias, AttributeName),
 4874                          Operator,
 4875                          ignore_if_null(ApplicationValue))
 4876        <=>
 4877        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType)
 4878        |
 4879        write_restriction_1(QueryId,
 4880                            CompileInstruction,
 4881                            RestrictionType,
 4882                            OdbcDataType,
 4883                            _,
 4884                            Schema,
 4885                            TableName,
 4886                            AttributeName,
 4887                            attribute(Schema, TableAlias, AttributeName),
 4888                            Operator,
 4889                            ignore_if_null(TableAlias, ApplicationValue)).
 4890
 4891write_restriction_between_attribute_and_if_not_var @
 4892        query_table_alias(_, Schema, TableName, TableAlias)
 4893        \
 4894        write_restriction(QueryId,
 4895                          CompileInstruction,
 4896                          RestrictionType,
 4897                          attribute(Schema, TableAlias, AttributeName),
 4898                          Operator,
 4899                          if_not_var(Variable))
 4900        <=>
 4901        atom(AttributeName),
 4902        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType)
 4903        |
 4904        write_restriction_1(QueryId,
 4905                            CompileInstruction,
 4906                            RestrictionType,
 4907                            OdbcDataType,
 4908                            _,
 4909                            Schema,
 4910                            TableName,
 4911                            AttributeName,
 4912                            attribute(Schema, TableAlias, AttributeName),
 4913                            Operator,
 4914                            if_not_var(Variable)).
 4915
 4916
 4917not_in_list_comparison_with_no_elements @
 4918        write_restriction(QueryId, CompileInstruction, RestrictionType, _, (\==), [])
 4919        <=>
 4920        true
 4921        |
 4922        write_sql(QueryId, CompileInstruction, RestrictionType, ['1 = 1'|T], T, [], []).
 4923
 4924write_list_comparison_with_collation @
 4925        query_table_alias(_, Schema, TableName, TableAlias)
 4926        \
 4927        write_restriction(QueryId, _CompileInstruction, RestrictionType, attribute(Schema, TableAlias, AttributeName), Operator, List)
 4928        <=>
 4929        is_list(List),
 4930        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType),
 4931        collatable_odbc_data_type(OdbcDataType),
 4932
 4933        ( Operator == (==) ->
 4934            ListOperator = 'IN'
 4935
 4936        ; Operator == (\==) ->
 4937            ListOperator = 'NOT IN'
 4938        )
 4939        |
 4940        % Duplicate the restriction to avoid the index scan that would result from
 4941        % using the collation comparison alone
 4942        % but only for SQL Server
 4943        ( collation(Schema, Collation)->
 4944           write_sql(QueryId, compile, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|T1], T1, [], []),
 4945           write_sql(QueryId, compile, RestrictionType, [' ', Collation, ' ', ListOperator, ' ('|T2], T2, [], []),
 4946           write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, List),
 4947           write_sql(QueryId, compile, RestrictionType, [') AND '|T3], T3, [], [])
 4948        ; otherwise->
 4949           true
 4950        ),
 4951        write_sql(QueryId, compile, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|T4], T4, [], []),
 4952        write_sql(QueryId, compile, RestrictionType, [' ', ListOperator, ' ('|T5], T5, [], []),
 4953        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, List),
 4954        write_sql(QueryId, compile, RestrictionType, [')'|T6], T6, [], []).
 4955
 4956write_list_comparison_without_collation @
 4957        query_table_alias(_, Schema, TableName, TableAlias)
 4958        \
 4959        write_restriction(QueryId, _CompileInstruction, RestrictionType, attribute(Schema, TableAlias, AttributeName), Operator, List)
 4960        <=>
 4961        is_list(List),
 4962        ( Operator == (==) ->
 4963            ListOperator = 'IN'
 4964
 4965        ; Operator == (\==) ->
 4966            ListOperator = 'NOT IN'
 4967        )
 4968        |
 4969        write_sql(QueryId, compile, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|T1], T1, [], []),
 4970        write_sql(QueryId, compile, RestrictionType, [' ', ListOperator, ' ('|T2], T2, [], []),
 4971        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, List),
 4972        write_sql(QueryId, compile, RestrictionType, [')'|T3], T3, [], []).
 4973
 4974write_runtime_list @
 4975        query_table_alias(_, Schema, TableName, TableAlias)
 4976        \
 4977        write_restriction(QueryId, _CompileInstruction, RestrictionType, attribute(Schema, TableAlias, AttributeName), Operator, list(List))
 4978        <=>
 4979        SubInstruction = not_empty(List),
 4980        OtherInstruction = empty(List),
 4981
 4982        ( Operator == (==) ->
 4983            ListOperator = 'IN'
 4984
 4985        ; Operator == (\==) ->
 4986            ListOperator = 'NOT IN'
 4987        ),
 4988        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType),
 4989
 4990        ( collatable_odbc_data_type(OdbcDataType), collation(Schema, Collation)->
 4991            true
 4992        ;
 4993            Collation = ''
 4994        ),
 4995        write_sql(QueryId, SubInstruction, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|T1], T1, [], []),
 4996
 4997        write_sql(QueryId,
 4998                  SubInstruction,
 4999                  RestrictionType,
 5000                  [' ', Collation, ' ', ListOperator, ' ('|T2],
 5001                  T2,
 5002                  [],
 5003                  []),
 5004        write_sql(QueryId,
 5005                  list(List),
 5006                  RestrictionType,
 5007                  [?|T3],
 5008                  T3,
 5009                  [odbc_parameter(Schema, TableName, AttributeName, _, where_value, _)],
 5010                  []),
 5011        write_sql(QueryId,
 5012                  SubInstruction,
 5013                  RestrictionType,
 5014                  [')'|T4],
 5015                  T4,
 5016                  [],
 5017                  []),
 5018        write_sql(QueryId,
 5019                  OtherInstruction,
 5020                  RestrictionType,
 5021                  ['1=1'|T5],
 5022                  T5,
 5023                  [],
 5024                  []).
 5025
 5026
 5027
 5028
 5029write_rhs_null_comparison @
 5030        write_restriction(QueryId, _CompileInstruction, RestrictionType, attribute(_, TableAlias, AttributeName), Operator, {null})
 5031        <=>
 5032        null_comparison_keywords(Operator, Keywords, Tail)
 5033        |
 5034        write_sql(QueryId, compile, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|Keywords], Tail, [], []).
 5035
 5036
 5037write_lhs_null_comparison @
 5038        write_restriction(QueryId, _CompileInstruction, RestrictionType, {null}, Operator, attribute(_, TableAlias, AttributeName))
 5039        <=>
 5040        null_comparison_keywords(Operator, Keywords, Tail)
 5041        |
 5042        write_sql(QueryId, compile, RestrictionType, [TableAlias, '.', attribute_name(AttributeName)|Keywords], Tail, [], []).
 5043
 5044
 5045null_comparison_keywords(==, [' IS NULL'|T], T).
 5046null_comparison_keywords(\==, [' IS NOT NULL'|T], T).
 5047
 5048
 5049write_restriction_between_attributes @
 5050        query_table_alias(_, _, TableNameLhs, TableAliasLhs)
 5051        \
 5052        write_restriction(QueryId,
 5053                          CompileInstruction,
 5054                          RestrictionType,
 5055                          attribute(_, TableAliasLhs, AttributeNameLhs),
 5056                          Operator,
 5057                          attribute(_, TableAliasRhs, AttributeNameRhs))
 5058        <=>
 5059        odbc_data_type(Schema, TableNameLhs, AttributeNameLhs, OdbcDataType)
 5060        |
 5061        write_restriction_1(QueryId,
 5062                            CompileInstruction,
 5063                            RestrictionType,
 5064                            OdbcDataType,
 5065                            _,
 5066                            Schema,
 5067                            TableNameLhs,
 5068                            AttributeNameLhs,
 5069                            attribute(_, TableAliasLhs, AttributeNameLhs),
 5070                            Operator,
 5071                            attribute(_, TableAliasRhs, AttributeNameRhs)).
 5072
 5073
 5074write_restriction_between_attribute_and_aggregation_sub_select @
 5075        query_table_alias(_, _, TableName, TableAlias)
 5076        \
 5077        write_restriction(QueryId,
 5078                          CompileInstruction,
 5079                          RestrictionType,
 5080                          attribute(Schema, TableAlias, AttributeName),
 5081                          Operator,
 5082                          aggregation_sub_query_sql(AggregationTableName, AggregationAttributeName, Sql, Tail, Inputs))
 5083        <=>
 5084        odbc_data_type(Schema, AggregationTableName, AggregationAttributeName, OdbcDataType)
 5085        |
 5086        Tail = [')'|NewTail],
 5087        write_restriction_1(QueryId,
 5088                            CompileInstruction,
 5089                            RestrictionType,
 5090                            OdbcDataType,
 5091                            _,
 5092                            Schema,
 5093                            TableName,
 5094                            AttributeName,
 5095                            attribute(Schema, TableAlias, AttributeName),
 5096                            Operator,
 5097                            tokens_and_parameters(['('|Sql], NewTail, Inputs)).
 5098
 5099
 5100write_restriction_between_aggregation_sub_select_and_attribute @
 5101        query_table_alias(_, _, TableName, TableAlias)
 5102        \
 5103        write_restriction(QueryId,
 5104                          CompileInstruction,
 5105                          RestrictionType,
 5106                          aggregation_sub_query_sql(AggregationTableName, AggregationAttributeName, Sql, Tail, Inputs),
 5107                          Operator,
 5108                          attribute(Schema, TableAlias, AttributeName))
 5109        <=>
 5110        odbc_data_type(Schema, AggregationTableName, AggregationAttributeName, OdbcDataType)
 5111        |
 5112        Tail = [')'],
 5113        write_restriction_1(QueryId,
 5114                            CompileInstruction,
 5115                            RestrictionType,
 5116                            OdbcDataType,
 5117                            _,
 5118                            Schema,
 5119                            TableName,
 5120                            AttributeName,
 5121                            ['('|Sql]-Inputs,
 5122                            Operator,
 5123                            attribute(Schema, TableAlias, AttributeName)).
 5124
 5125
 5126write_restriction_between_expression_and_aggregation_sub_select @
 5127        write_restriction(QueryId,
 5128                          CompileInstruction,
 5129                          RestrictionType,
 5130                          Expression,
 5131                          Operator,
 5132                          aggregation_sub_query_sql(AggregationTableName, AggregationAttributeName, Sql, Tail, Inputs))
 5133        <=>
 5134        odbc_data_type(Schema, AggregationTableName, AggregationAttributeName, OdbcDataType)
 5135        |
 5136        Tail = [')'|NewTail],
 5137        write_restriction_1(QueryId,
 5138                            CompileInstruction,
 5139                            RestrictionType,
 5140                            OdbcDataType,
 5141                            _,
 5142                            Schema,
 5143                            AggregationTableName,
 5144                            AggregationAttributeName,
 5145                            Expression,
 5146                            Operator,
 5147                            tokens_and_parameters(['('|Sql], NewTail, Inputs)).
 5148
 5149
 5150write_restriction_between_aggregation_sub_select_and_expression @
 5151        write_restriction(QueryId,
 5152                          CompileInstruction,
 5153                          RestrictionType,
 5154                          aggregation_sub_query_sql(AggregationTableName, AggregationAttributeName, Sql, Tail, Inputs),
 5155                          Operator,
 5156                          Expression)
 5157        <=>
 5158        odbc_data_type(Schema, AggregationTableName, AggregationAttributeName, OdbcDataType)
 5159        |
 5160        Tail = [')'|NewTail],
 5161        write_restriction_1(QueryId,
 5162                            CompileInstruction,
 5163                            RestrictionType,
 5164                            OdbcDataType,
 5165                            _,
 5166                            Schema,
 5167                            AggregationTableName,
 5168                            AggregationAttributeName,
 5169                            tokens_and_parameters(['('|Sql], NewTail, Inputs),
 5170                            Operator,
 5171                            Expression).
 5172
 5173
 5174write_restriction_between_expressions @
 5175        write_restriction(QueryId, CompileInstruction, RestrictionType, LhsExpression, Operator, RhsExpression)
 5176        <=>
 5177        RestrictionType \== having   % Could be an aggregation e.g. sum(x) - leave those for the HAVING phase
 5178        |
 5179        ( representative_attribute(LhsExpression+RhsExpression, Schema, TableName, AttributeName) ->
 5180            true
 5181        ; otherwise ->
 5182            throw(format('Cannot find attribute to determine expression data type in ~w or in ~w', [LhsExpression, RhsExpression]))
 5183        ),
 5184        ( odbc_data_type(Schema, TableName, AttributeName, OdbcDataType)->
 5185            true
 5186        ; otherwise->
 5187            throw(format('Could not determine the type of ~w.~w', [TableName, AttributeName]))
 5188        ),
 5189        write_restriction_1(QueryId,
 5190                            CompileInstruction,
 5191                            RestrictionType,
 5192                            OdbcDataType,
 5193                            _,
 5194                            Schema,
 5195                            TableName,
 5196                            AttributeName,
 5197                            LhsExpression,
 5198                            Operator,
 5199                            RhsExpression).
 5200
 5201
 5202representative_attribute_1 @
 5203        % Find an attribute to determine the data type of Expression
 5204        query_table_alias(_, Schema, TableName, TableAlias)
 5205        \
 5206        representative_attribute(attribute(Schema, TableAlias, AttributeName), RepresentativeSchema, RepresentativeTableName, RepresentativeAttributeName)
 5207        <=>
 5208        RepresentativeSchema = Schema,
 5209        RepresentativeTableName = TableName,
 5210        RepresentativeAttributeName = AttributeName.
 5211
 5212representative_attribute_2 @
 5213        representative_attribute(Expression, Schema, TableName, AttributeName)
 5214        <=>
 5215        nonvar(Expression),
 5216        Expression =.. [_|L],
 5217
 5218        ( L = [Lhs, Rhs] ->
 5219            ( representative_attribute(Lhs, Schema, TableName, AttributeName)
 5220            ; representative_attribute(Rhs, Schema, TableName, AttributeName)
 5221            )
 5222        ; L = [Expr] ->
 5223            representative_attribute(Expr, Schema, TableName, AttributeName)
 5224        ).
 5225
 5226
 5227write_having_comparison_between_aggregation_and_null @
 5228        query_table_alias(QueryId, Schema, _, TableAlias),
 5229        attribute_binding(QueryId, attribute(Schema, TableAlias, Aggregation), Variable)
 5230        \
 5231        write_restriction(QueryId, CompileInstruction, RestrictionType, Variable, Operator, {null})
 5232        <=>
 5233        not_a_singleton(Variable),
 5234        null_comparison_keywords(Operator, Keywords, Tail),
 5235        functor(Aggregation, Functor, 1),
 5236        aggregation_operator(Functor),
 5237        arg(1, Aggregation, AttributeName)
 5238        |
 5239        write_sql(QueryId, CompileInstruction, RestrictionType, [Functor, '(', TableAlias, '.', attribute_name(AttributeName), ')'|Keywords], Tail, [], []).
 5240
 5241write_having_comparison_between_null_and_aggregation @
 5242        query_table_alias(QueryId, Schema, _, TableAlias),
 5243        attribute_binding(QueryId, attribute(Schema, TableAlias, Aggregation), Variable)
 5244        \
 5245        write_restriction(QueryId, CompileInstruction, RestrictionType, {null}, Operator, Variable)
 5246        <=>
 5247        not_a_singleton(Variable),
 5248        null_comparison_keywords(Operator, Keywords, Tail),
 5249        functor(Aggregation, Functor, 1),
 5250        aggregation_operator(Functor),
 5251        arg(1, Aggregation, AttributeName)
 5252        |
 5253        write_sql(QueryId, CompileInstruction, RestrictionType, [Functor, '(', TableAlias, '.', attribute_name(AttributeName), ')'|Keywords], Tail, [], []).
 5254
 5255write_having_comparison_between_aggregation_and_expression @
 5256        query_table_alias(QueryId, Schema, TableName, TableAlias),
 5257        attribute_binding(QueryId, attribute(Schema, TableAlias, Aggregation), Variable)
 5258        \
 5259        write_restriction(QueryId, CompileInstruction, RestrictionType, Variable, Operator, Expression)
 5260        <=>
 5261        not_a_singleton(Variable),
 5262        functor(Aggregation, Functor, 1),
 5263        aggregation_operator(Functor),
 5264        arg(1, Aggregation, AttributeName),
 5265        ( nonvar(Expression),
 5266          Expression = ignore_if_null(ApplicationValue) ->
 5267            IgnoreExpression =.. [Functor, TableAlias, AttributeName],
 5268            E = ignore_if_null(IgnoreExpression, ApplicationValue)
 5269
 5270        ; otherwise ->
 5271            E = Expression
 5272        ),
 5273        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType),
 5274
 5275        ( Functor == count ->
 5276            OdbcDataTypeOverride = integer
 5277
 5278        ; otherwise ->
 5279            true
 5280        )
 5281        |
 5282        write_restriction_1(QueryId,
 5283                            CompileInstruction,
 5284                            RestrictionType,
 5285                            OdbcDataType,
 5286                            OdbcDataTypeOverride,
 5287                            Schema,
 5288                            TableName,
 5289                            AttributeName,
 5290                            tokens_and_parameters([Functor, '(', TableAlias, '.', attribute_name(AttributeName), ')'|Tail], Tail, []),
 5291                            Operator,
 5292                            E).
 5293
 5294write_having_comparison_between_expression_and_aggregation @
 5295        query_table_alias(QueryId, Schema, TableName, TableAlias),
 5296        attribute_binding(QueryId, attribute(Schema, TableAlias, Aggregation), Variable)
 5297        \
 5298        write_restriction(QueryId, CompileInstruction, RestrictionType, Expression, Operator, Variable)
 5299        <=>
 5300        functor(Aggregation, Functor, 1),
 5301        aggregation_operator(Functor),
 5302        arg(1, Aggregation, AttributeName),
 5303        ( nonvar(Expression),
 5304          Expression = ignore_if_null(ApplicationValue) ->
 5305            IgnoreExpression =.. [Functor, TableAlias, AttributeName],
 5306            E = ignore_if_null(IgnoreExpression, ApplicationValue)
 5307
 5308        ; otherwise ->
 5309            E = Expression
 5310        ),
 5311        odbc_data_type(Schema, TableName, AttributeName, OdbcDataType),
 5312
 5313        ( Functor == count ->
 5314            OdbcDataTypeOverride = integer
 5315
 5316        ; otherwise ->
 5317            true
 5318        )
 5319        |
 5320        write_restriction_1(QueryId,
 5321                            CompileInstruction,
 5322                            RestrictionType,
 5323                            OdbcDataType,
 5324                            OdbcDataTypeOverride,
 5325                            Schema,
 5326                            TableName,
 5327                            AttributeName,
 5328                            E,
 5329                            Operator,
 5330                            tokens_and_parameters([Functor, '(', TableAlias, '.', attribute_name(AttributeName), ')'|Tail], Tail, [])).
 5331
 5332write_restriction_with_collation @  % Prolog-style atom matching i.e. case-sensitive
 5333        write_restriction_1(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs, ComparisonOperator, Rhs)
 5334        <=>
 5335        ( nonvar(OdbcDataTypeOverride) ->
 5336            collatable_odbc_data_type(OdbcDataTypeOverride)
 5337
 5338        ; collatable_odbc_data_type(OdbcDataType) ->
 5339            true
 5340        ),
 5341
 5342        collatable_operator(ComparisonOperator),
 5343        prolog_to_sql_comparison_operator(Schema, ComparisonOperator, BaseSqlOperator, _)
 5344        |
 5345        % Need to duplicate the restriction to avoid the index scan that would result from
 5346        % using the collation comparison alone
 5347        % But only in SQL Server
 5348        ( RestrictionType == where ->
 5349            instruction_conjunction(CompileInstruction, if_not_null(Variable), C1)
 5350        ; otherwise->
 5351            C1 = CompileInstruction
 5352        ),
 5353        instruction_conjunction(CompileInstruction, if_null(Variable), C2),
 5354        ( collation(Schema, Collation)->
 5355            atomic_list_concat([Collation, ' ', BaseSqlOperator], SqlOperator),
 5356            write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs),
 5357            ( ( var(Rhs)->
 5358                  Variable = Rhs
 5359              ; Rhs = if_not_var(Variable)->
 5360                  true
 5361              ; Rhs = equality_restriction(Variable) ->
 5362                  true
 5363              )->
 5364                % Either "= RHS" or " IS NULL" if RHS is {null} at runtime
 5365                write_sql(QueryId, C1, RestrictionType, [' ', SqlOperator, ' '|T1], T1, [], []),
 5366                write_restriction_expression(QueryId, C1, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs),
 5367                ( RestrictionType == where ->
 5368                    write_sql(QueryId, C2, RestrictionType, [' IS NULL'|T2], T2, [], [])
 5369                ; otherwise->
 5370                    true
 5371                )
 5372            ; otherwise->
 5373                write_sql(QueryId, CompileInstruction, RestrictionType, [' ', SqlOperator, ' '|T3], T3, [], []),
 5374                write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs)
 5375            ),
 5376            write_sql(QueryId, CompileInstruction, RestrictionType, [' AND '|T4], T4, [], [])
 5377        ; otherwise->
 5378            true
 5379        ),
 5380        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs),
 5381        ( ( var(Rhs)->
 5382              Variable = Rhs
 5383           ; Rhs = if_not_var(Variable)->
 5384                  true
 5385          ; Rhs = equality_restriction(Variable) ->
 5386              true
 5387          )->
 5388            % Either "= RHS" or " IS NULL" if RHS is {null} at runtime
 5389            write_sql(QueryId, C1, RestrictionType, [' ', BaseSqlOperator, ' '|T5], T5, [], []),
 5390            write_restriction_expression(QueryId, C1, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs),
 5391            ( RestrictionType == where ->
 5392                write_sql(QueryId, C2, RestrictionType, [' IS NULL'|T6], T6, [], [])
 5393            ; otherwise->
 5394                true
 5395            )
 5396        ; otherwise->
 5397            write_sql(QueryId, CompileInstruction, RestrictionType, [' ', BaseSqlOperator, ' '|T7], T7, [], []),
 5398            write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs)
 5399        ).
 5400
 5401
 5402write_restriction_without_collation @
 5403        write_restriction_1(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs, ComparisonOperator, Rhs)
 5404        <=>
 5405        prolog_to_sql_comparison_operator(Schema, ComparisonOperator, SqlOperator, _)
 5406        |
 5407        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs),
 5408
 5409        % This sets the RHS to be a 'LikeParameter'. We can undo this later if we discover the RHS is an expression
 5410        ( is_like_operator(ComparisonOperator, LikeOdbcDataType) ->
 5411            OdbcDataTypeOverride = LikeOdbcDataType
 5412        ; otherwise ->
 5413            true
 5414        ),
 5415
 5416        ( ( var(Rhs)->
 5417              Variable = Rhs
 5418           ; Rhs = if_not_var(Variable)->
 5419              true
 5420          ; Rhs = equality_restriction(Variable) ->
 5421              true
 5422          )->
 5423            ( RestrictionType == where ->
 5424                instruction_conjunction(CompileInstruction, if_not_null(Variable), C1)
 5425            ; otherwise->
 5426                C1 = CompileInstruction
 5427            ),
 5428            instruction_conjunction(CompileInstruction, if_null(Variable), C2),
 5429            write_sql(QueryId, C1, RestrictionType, [' ', SqlOperator, ' '|T1], T1, [], []),
 5430            write_restriction_expression(QueryId, C1, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs),
 5431            ( RestrictionType == where ->
 5432                write_sql(QueryId, C2, RestrictionType, [' IS NULL'|T2], T2, [], [])
 5433            ; otherwise->
 5434                true
 5435            )
 5436        ; otherwise->
 5437            write_sql(QueryId, CompileInstruction, RestrictionType, [' ', SqlOperator, ' '|T3], T3, [], []),
 5438            write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs)
 5439        ).
 5440
 5441
 5442% prolog_to_sql_comparison_operator(Schema,
 5443%                                   ComparisonOperator,
 5444%                                   SqlOperator,
 5445%                                   InverseComparisonOperator)
 5446
 5447prolog_to_sql_comparison_operator(_, <, <, >=).
 5448prolog_to_sql_comparison_operator(_, =<, <=, >).
 5449prolog_to_sql_comparison_operator(_, ==, =, \==).
 5450prolog_to_sql_comparison_operator(_, =:=, =, =\=).
 5451prolog_to_sql_comparison_operator(Schema, =~, Operator, \=~):-
 5452        (dbms(Schema, 'Microsoft SQL Server')->
 5453           Operator = 'LIKE'
 5454        ; dbms(Schema, 'SQLite')->
 5455           Operator = 'LIKE'
 5456        ; dbms(Schema, 'PostgreSQL')->
 5457           Operator = 'ILIKE'
 5458        ).
 5459prolog_to_sql_comparison_operator(Schema, \=~, Operator, =~):-
 5460        ( dbms(Schema, 'Microsoft SQL Server')->
 5461            Operator = 'NOT LIKE'
 5462        ; dbms(Schema, 'SQLite')->
 5463            Operator = 'NOT LIKE'
 5464        ; dbms(Schema, 'PostgreSQL')->
 5465            Operator = 'NOT ILIKE'
 5466        ).
 5467prolog_to_sql_comparison_operator(_, \==, <>, ==).
 5468prolog_to_sql_comparison_operator(_, =\=, <>, =:=).
 5469prolog_to_sql_comparison_operator(_, >=, >=, <).
 5470prolog_to_sql_comparison_operator(_, >, >, =<).
 5471
 5472
 5473collatable_odbc_data_type(char(_)).
 5474collatable_odbc_data_type(varchar(_)).
 5475collatable_odbc_data_type(longvarchar).
 5476
 5477
 5478collatable_operator(Operator):-
 5479        Operator \== (=~).
 5480
 5481
 5482is_like_operator((=~), varchar(128)).
 5483
 5484
 5485collation(Schema, 'COLLATE Latin1_General_CS_AS'):-  % Make CQL case-sensitive
 5486        dbms(Schema, 'Microsoft SQL Server').
 5487
 5488collation(Schema, _):-
 5489        ( dbms(Schema, 'PostgreSQL')->
 5490            fail
 5491        ; dbms(Schema, 'SQLite')->
 5492            fail
 5493        ).
 5494
 5495write_restriction_expression_1 @
 5496        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, _, _, _, _, tokens_and_parameters(Tokens, Tail, OdbcParameters))
 5497        <=>
 5498        write_sql(QueryId,
 5499                  CompileInstruction,
 5500                  RestrictionType,
 5501                  Tokens,
 5502                  Tail,
 5503                  OdbcParameters,
 5504                  []).
 5505
 5506write_restriction_expression_2 @
 5507        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, _, _, _, _, attribute(_, TableAlias, AttributeName))
 5508        <=>
 5509        write_sql(QueryId,
 5510                  CompileInstruction,
 5511                  RestrictionType,
 5512                  [TableAlias, '.', attribute_name(AttributeName)|T],
 5513                  T,
 5514                  [],
 5515                  []).
 5516
 5517write_restriction_expression_3 @
 5518        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, OdbcDataTypeOverride, Schema, TableName, AttributeName, equality_restriction(Variable))
 5519        <=>
 5520        write_sql(QueryId,
 5521                  CompileInstruction,
 5522                  RestrictionType,
 5523                  [?|T],
 5524                  T,
 5525                  [odbc_parameter(Schema, TableName, AttributeName, Variable, where_value, OdbcDataTypeOverride)],
 5526                  []).
 5527
 5528% This is a ignore_if_null against an aggregation
 5529write_restriction_expression_4a @
 5530        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, OdbcDataTypeOverride, Schema, TableName, AttributeName, ignore_if_null(Aggregation, Variable))
 5531        <=>
 5532        functor(Aggregation, Functor, 2),
 5533        aggregation_operator(Functor)
 5534        |
 5535        arg(1, Aggregation, TableAlias),
 5536        arg(2, Aggregation, AttributeName),
 5537        write_sql(QueryId,
 5538                  CompileInstruction,
 5539                  RestrictionType,
 5540                  ['COALESCE(?, ', Functor, '(', TableAlias, '.', attribute_name(AttributeName), '))'|T],
 5541                  T,
 5542                  [odbc_parameter(Schema, TableName, AttributeName, Variable, where_value, OdbcDataTypeOverride)],
 5543                  []).
 5544
 5545write_restriction_expression_4 @
 5546        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, OdbcDataTypeOverride, Schema, TableName, AttributeName, ignore_if_null(TableAlias, Variable))
 5547        <=>
 5548        write_sql(QueryId,
 5549                  CompileInstruction,
 5550                  RestrictionType,
 5551                  ['COALESCE(?, ', TableAlias, '.', attribute_name(AttributeName), ')'|T],
 5552                  T,
 5553                  [odbc_parameter(Schema, TableName, AttributeName, Variable, where_value, OdbcDataTypeOverride)],
 5554                  []).
 5555
 5556write_restriction_expression_5 @
 5557        attribute_binding(QueryId, Attribute, Variable)
 5558        \
 5559        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Variable)
 5560        <=>
 5561        var(Variable)
 5562        |
 5563        where_restriction_variable(Variable),
 5564        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Attribute).
 5565
 5566write_restriction_expression_6 @
 5567        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _, OdbcDataTypeOverride, Schema, TableName, AttributeName, Variable)
 5568        <=>
 5569        atomic_application_value(Variable)
 5570        |
 5571        write_sql(QueryId,
 5572                  CompileInstruction,
 5573                  RestrictionType,
 5574                  [?|T],
 5575                  T,
 5576                  [odbc_parameter(Schema, TableName, AttributeName, Variable, where_value, OdbcDataTypeOverride)],
 5577                  []).
 5578
 5579write_restriction_expression_7 @
 5580        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Expression)
 5581        <=>
 5582        Expression =.. [Operator, Rhs],
 5583        restriction_prefix_operator(Operator)
 5584        |
 5585        write_sql(QueryId, CompileInstruction,  RestrictionType, [Operator|T], T, [], []),
 5586        % We unset the OdbcDataTypeOverride here
 5587        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs).
 5588
 5589write_restriction_expression_8 @
 5590        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Expression)
 5591        <=>
 5592        Expression =.. [Operator, Lhs, Rhs],
 5593        restriction_expression_operator(Operator)
 5594        |
 5595        ( dbms(Schema, 'SQLite') ->
 5596            write_sql(QueryId, CompileInstruction, RestrictionType, ['(1.0*'|T1], T1, [], [])
 5597        ; otherwise->
 5598            write_sql(QueryId, CompileInstruction, RestrictionType, ['('|T1], T1, [], [])
 5599        ),
 5600        % We unset the OdbcDataTypeOverride here
 5601        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Lhs),
 5602        write_sql(QueryId, CompileInstruction, RestrictionType, [')'|T2], T2, [], []),
 5603        write_sql(QueryId, CompileInstruction, RestrictionType, [Operator|T3], T3, [], []),
 5604        ( dbms(Schema, 'SQLite') ->
 5605            write_sql(QueryId, CompileInstruction, RestrictionType, ['(1.0*'|T4], T4, [], [])
 5606        ; otherwise->
 5607            write_sql(QueryId, CompileInstruction, RestrictionType, ['('|T4], T4, [], [])
 5608        ),
 5609        % We unset the OdbcDataTypeOverride here
 5610        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, Rhs),
 5611        write_sql(QueryId, CompileInstruction, RestrictionType, [')'|T5], T5, [], []).
 5612
 5613write_restriction_expression_9 @
 5614        write_restriction_expression(QueryId, CompileInstruction, RestrictionType, _OdbcDataType, OdbcDataTypeOverride, Schema, TableName, AttributeName, if_not_var(Var))
 5615        <=>
 5616        instruction_conjunction(CompileInstruction, if_not_var(Var), NewInstruction),
 5617        write_sql(QueryId,
 5618                  NewInstruction,
 5619                  RestrictionType,
 5620                  [?|T],
 5621                  T,
 5622                  [odbc_parameter(Schema, TableName, AttributeName, Var, where_value, OdbcDataTypeOverride)],
 5623                  []).
 5624
 5625
 5626write_restriction_expression_10 @
 5627        write_restriction_expression(_, _, _, _, _, _, _, _, Expression)
 5628        <=>
 5629        throw(format('Bad restriction expression: ~w', [Expression])).
 5630
 5631
 5632restriction_prefix_operator(+).
 5633restriction_prefix_operator(-).
 5634
 5635restriction_expression_operator(+).
 5636restriction_expression_operator(-).
 5637restriction_expression_operator(/).
 5638restriction_expression_operator(*).
 5639
 5640
 5641write_sub_query @
 5642        write_restriction_tree(QueryId, RestrictionType, sub_query(SubQueryType, Sql, SqlTail, SubQueryInputs))
 5643        <=>
 5644        ( SubQueryType == exists ->
 5645            Token = 'EXISTS'
 5646
 5647        ; SubQueryType == (\+ exists) ->
 5648            Token = 'NOT EXISTS'
 5649        )
 5650        |
 5651        SqlTail = [')'|T],
 5652        write_sql(QueryId, compile, RestrictionType, [Token,  ' ('|Sql], T, SubQueryInputs, []).
 5653
 5654
 5655write_in_list_1 @
 5656        next_in_list_value_needs_comma(QueryId)
 5657        \
 5658        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, [ApplicationValue|ApplicationValues])
 5659        <=>
 5660        write_sql(QueryId, compile, RestrictionType, [', ?'|T], T, [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, where_value, _)], []),
 5661        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, ApplicationValues).
 5662
 5663
 5664write_in_list_2 @
 5665        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, [ApplicationValue|ApplicationValues])
 5666        <=>
 5667        write_sql(QueryId, compile, RestrictionType, [?|T], T, [odbc_parameter(Schema, TableName, AttributeName, ApplicationValue, where_value, _)], []),
 5668        next_in_list_value_needs_comma(QueryId),
 5669        write_in_list(QueryId, RestrictionType, Schema, TableName, AttributeName, ApplicationValues).
 5670
 5671
 5672write_in_list_3 @
 5673        write_in_list(QueryId, _, _, _, _, []),
 5674        next_in_list_value_needs_comma(QueryId)
 5675        <=>
 5676        true.
 5677
 5678
 5679write_group_by @
 5680        group_by(QueryId, _)
 5681        \
 5682        phase(QueryId, group_by)
 5683        <=>
 5684        write_sql(QueryId, compile, having, [' GROUP BY '|T], T, [], []),
 5685        write_group_bys(QueryId),
 5686        phase(QueryId, having).
 5687
 5688
 5689no_group_by @
 5690        phase(QueryId, group_by)
 5691        <=>
 5692        phase(QueryId, having).
 5693
 5694
 5695write_group_bys @
 5696        write_group_bys(QueryId)
 5697        \
 5698        attribute_for_group_by(QueryId, TableAlias, AttributeName, GroupBy),
 5699        group_by(QueryId, GroupBy)
 5700        <=>
 5701        write_group_by_attribute(QueryId, [TableAlias, '.', AttributeName|T], T).
 5702
 5703
 5704write_group_by_attribute_with_trailing_comma @
 5705        next_group_by_attribute_needs_comma(QueryId)
 5706        \
 5707        write_group_by_attribute(QueryId, SqlTokens, Tail)
 5708        <=>
 5709        write_sql(QueryId, compile, having, [', '|SqlTokens], Tail, [], []).
 5710
 5711
 5712write_group_by_attribute_without_trailing_comma @
 5713        write_group_by_attribute(QueryId, SqlTokens, Tail)
 5714        <=>
 5715        write_sql(QueryId, compile, having, SqlTokens, Tail, [], []),
 5716        next_group_by_attribute_needs_comma(QueryId).
 5717
 5718
 5719should_not_be_any_group_by_constraints_left_over @
 5720        check_for_orphan_group_bys,
 5721        group_by(_, GroupBy),
 5722        original_cql(Cql)
 5723        <=>
 5724        throw(format('Unused GROUP BY ~w in CQL: ~w', [GroupBy, Cql])).
 5725
 5726
 5727write_order_by @
 5728        order_bys(QueryId, OrderBys)
 5729        \
 5730        phase(QueryId, order_by)
 5731        <=>
 5732        OrderBys \== []
 5733        |
 5734        write_sql(QueryId, compile, having, [' ORDER BY '|T], T, [], []),
 5735        write_order_bys(QueryId, OrderBys),
 5736        phase(QueryId, union).
 5737
 5738
 5739no_order_by @
 5740        phase(QueryId, order_by)
 5741        <=>
 5742        phase(QueryId, union).
 5743
 5744
 5745write_order_bys @
 5746        write_order_bys(QueryId, [OrderBy|OrderBys])
 5747        <=>
 5748        write_order_by(QueryId, OrderBy),
 5749        write_order_bys(QueryId, OrderBys).
 5750
 5751
 5752clean_up_write_order_bys @
 5753        write_order_bys(_, [])
 5754        <=>
 5755        true.
 5756
 5757
 5758write_order_by_aggregate @
 5759        write_order_by(QueryId, OrderBy),
 5760        attribute_for_order_by(QueryId, TableAlias, AggregationTerm, Variable)
 5761        <=>
 5762        AggregationTerm =.. [AggregationOperator, AttributeName],
 5763        aggregation_operator(AggregationOperator),
 5764
 5765        ( OrderBy == +(Variable) ->
 5766            Direction = 'ASC'
 5767
 5768        ; OrderBy == -(Variable) ->
 5769            Direction = 'DESC'
 5770        ),
 5771        %map_database_atom(AggregationOperator, AggregationOperatorUc)
 5772        upcase_atom(AggregationOperator, AggregationOperatorUc)
 5773        |
 5774        not_a_singleton(Variable),
 5775        write_order_by_attribute(QueryId, [AggregationOperatorUc, '(', TableAlias, '.', attribute_name(AttributeName), ') ', Direction|T], T).
 5776
 5777
 5778write_order_by @
 5779        write_order_by(QueryId, OrderBy),
 5780        attribute_for_order_by(QueryId, TableAlias, AttributeName, Variable)
 5781        <=>
 5782        ( OrderBy == +(Variable) ->
 5783            Direction = 'ASC'
 5784
 5785        ; OrderBy == -(Variable) ->
 5786            Direction = 'DESC'
 5787        )
 5788        |
 5789        not_a_singleton(Variable),
 5790        write_order_by_attribute(QueryId, [TableAlias, '.', attribute_name(AttributeName), ' ', Direction|T], T).
 5791
 5792
 5793
 5794write_order_by_attribute_with_trailing_comma @
 5795        next_order_by_attribute_needs_comma(QueryId)
 5796        \
 5797        write_order_by_attribute(QueryId, SqlTokens, Tail)
 5798        <=>
 5799        write_sql(QueryId, compile, having, [', '|SqlTokens], Tail, [], []).
 5800
 5801
 5802write_order_by_attribute_without_trailing_comma @
 5803        write_order_by_attribute(QueryId, SqlTokens, Tail)
 5804        <=>
 5805        write_sql(QueryId, compile, having, SqlTokens, Tail, [], []),
 5806        next_order_by_attribute_needs_comma(QueryId).
 5807
 5808
 5809should_not_be_any_write_order_by_constraints_left_over @
 5810        check_for_orphan_order_bys,
 5811        write_order_by(_, OrderBy),
 5812        original_cql(Cql)
 5813        <=>
 5814        throw(format('Unused ORDER BY ~w in CQL: ~w', [OrderBy, Cql])).
 5815
 5816
 5817in_line_formats @
 5818        prior_to_execution \ in_line_format(_, Format, FormatArgs, ApplicationValue) <=>  format(atom(ApplicationValue), Format, FormatArgs).
 5819        prior_to_execution <=> true.
 5820
 5821
 5822postgres_identity @
 5823        number_of_rows_affected(QueryId, _, _)
 5824        \
 5825        postgres_identity(QueryId, ReturnedIdentity),
 5826        cql_identity(QueryId, _, Identity)
 5827        <=>
 5828        Identity = ReturnedIdentity.
 5829
 5830ignored_postgres_identity @
 5831        number_of_rows_affected(QueryId, _, _)
 5832        \
 5833        postgres_identity(QueryId, _)
 5834        <=>
 5835        true.
 5836
 5837identity_sql_server @
 5838        number_of_rows_affected(QueryId, Connection, _),
 5839        cql_statement_location(FileName, LineNumber)
 5840        \
 5841        cql_identity(QueryId, Schema, Identity)
 5842        <=>
 5843        dbms(Schema, 'Microsoft SQL Server'),
 5844        odbc_query(Connection, 'SELECT CAST(@@IDENTITY AS INTEGER)', row(ScopeIdentity))
 5845        |
 5846        ( integer(ScopeIdentity) ->
 5847            Identity = ScopeIdentity,
 5848            get_transaction_context(TransactionId, _, AccessToken, _, _),
 5849            cql_access_token_to_user_id(AccessToken, UserId),
 5850            cql_log([], informational, 'CQL\t~w\t~w\t   Inserted row has identity ~w\t(~w:~w)', [UserId, TransactionId, Identity, FileName, LineNumber])
 5851        ; otherwise ->
 5852            cql_error(bad_identity, 'Integer identity value expected but got ~q', [ScopeIdentity])
 5853        ).
 5854
 5855identity_sqlite @
 5856        number_of_rows_affected(QueryId, Connection, _),
 5857        cql_statement_location(FileName, LineNumber)
 5858        \
 5859        cql_identity(QueryId, Schema, Identity)
 5860        <=>
 5861        dbms(Schema, 'SQLite'),
 5862        odbc_query(Connection, 'SELECT CAST(last_insert_rowid() AS INTEGER)', row(ScopeIdentity))
 5863        |
 5864        ( integer(ScopeIdentity) ->
 5865            Identity = ScopeIdentity,
 5866            get_transaction_context(TransactionId, _, AccessToken, _, _),
 5867            cql_access_token_to_user_id(AccessToken, UserId),
 5868            cql_log([], informational, 'CQL\t~w\t~w\t   Inserted row has identity ~w\t(~w:~w)', [UserId, TransactionId, Identity, FileName, LineNumber])
 5869        ; otherwise ->
 5870            cql_error(bad_identity, 'Integer identity value expected but got ~q', [ScopeIdentity])
 5871        ).
 5872
 5873rows_affected @
 5874        number_of_rows_affected(QueryId, _, N)
 5875        \
 5876        row_count(QueryId, RowCount)
 5877        <=>
 5878        RowCount = N.
 5879
 5880post_state_change_statistics @
 5881        number_of_rows_affected(QueryId, _, N)
 5882        \
 5883        cql_state_change_statistics_sql(QueryId, Schema, TableName, update, _, StateChangeAttributeNames, OdbcParameters, _)
 5884        <=>
 5885        process_statistics_post_state_changes(Schema, TableName, StateChangeAttributeNames, OdbcParameters, N).
 5886
 5887number_of_rows_affected_cleanup @
 5888        number_of_rows_affected(QueryId, _, _),  cql_state_change_statistics_sql(QueryId, _, _, _, _, _, _, _) <=> true.
 5889        number_of_rows_affected(_, _, _) <=> true.
 5890
 5891
 5892write_sql @
 5893        sql_statement(QueryId, TokensSoFar, TokensTail, FromTokensSoFar, FromTail, RestrictionTokensSoFar, RestrictionTail, ExistingOdbcParameters, ExistingFromParameters, ExistingOutputs),
 5894        write_sql(QueryId, CompileInstruction, Position, AddTokens, AddTail, OdbcParameters, Outputs)
 5895        <=>
 5896        ( CompileInstruction == compile->
 5897            Addition = AddTokens,
 5898            AdditionTail = AddTail,
 5899            ( Position \== top->
 5900                append(ExistingFromParameters, OdbcParameters, NewFromParameters),
 5901                NewOdbcParameters = ExistingOdbcParameters
 5902            ; otherwise->
 5903                ( var(OdbcParameters)->
 5904                    append(ExistingOdbcParameters, [compile:OdbcParameters], NewOdbcParameters)
 5905                ; otherwise->
 5906                    append(ExistingOdbcParameters, OdbcParameters, NewOdbcParameters)
 5907                ),
 5908                NewFromParameters = ExistingFromParameters
 5909            )
 5910        ; otherwise->
 5911            % FIXME: This is where to keep the tail around so we can flatten quickly at runtime
 5912            Addition = [CompileInstruction:AddTokens|AdditionTail],
 5913            AddTail = [],
 5914            ( OdbcParameters == []->
 5915                NewOdbcParameters = ExistingOdbcParameters,
 5916                NewFromParameters = ExistingFromParameters
 5917            ; otherwise->
 5918                ( Position \== top->
 5919                    append(ExistingFromParameters, [CompileInstruction:OdbcParameters], NewFromParameters),
 5920                    NewOdbcParameters = ExistingOdbcParameters
 5921                ; otherwise->
 5922                    append(ExistingOdbcParameters, [CompileInstruction:OdbcParameters], NewOdbcParameters),
 5923                    NewFromParameters = ExistingFromParameters
 5924                )
 5925            )
 5926        ),
 5927        ( Position == join ->
 5928            FromTail = Addition,
 5929            NewFromTail = AdditionTail,
 5930            NewTokensTail = TokensTail,
 5931            NewRestrictionTail = RestrictionTail
 5932        ; Position == top ->
 5933            TokensTail = Addition,
 5934            NewTokensTail = AdditionTail,
 5935            NewFromTail = FromTail,
 5936            NewRestrictionTail = RestrictionTail
 5937        ; otherwise->
 5938            NewRestrictionTail = AdditionTail,
 5939            RestrictionTail = Addition,
 5940            NewTokensTail = TokensTail,
 5941            NewFromTail = FromTail
 5942        ),
 5943        ( CompileInstruction == compile ->
 5944            append(ExistingOutputs, Outputs, NewOutputs)
 5945        ; Outputs == []->
 5946            NewOutputs = ExistingOutputs
 5947        ; otherwise->
 5948            append(ExistingOutputs, [CompileInstruction:Outputs], NewOutputs)
 5949        ),
 5950        sql_statement(QueryId, TokensSoFar, NewTokensTail, FromTokensSoFar, NewFromTail, RestrictionTokensSoFar, NewRestrictionTail, NewOdbcParameters, NewFromParameters, NewOutputs).
 5951
 5952
 5953instantiate_aggregation_sub_query @
 5954        query(SubQueryId, _, sub_query)
 5955        \
 5956        phase(SubQueryId, union),
 5957        sql_statement(SubQueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, OdbcParameters, FromParameters, [output(_, TableName, AttributeName, _)]),
 5958        aggregation_sub_query(SubQueryId, AggregationTableName, AggregationAttributeName, SubQuerySqlTokens, SubQueryTail, SubQueryOdbcParameters)
 5959        <=>
 5960        AggregationTableName = TableName,
 5961        AggregationAttributeName = AttributeName,
 5962        TokensTail = SqlFromTokens,
 5963        FromTail = SqlRestrictionTokens,
 5964        SubQueryTail = RestrictionTail,
 5965        SubQuerySqlTokens = SqlTokens,
 5966        append(OdbcParameters, FromParameters, SubQueryOdbcParameters).
 5967
 5968instantiate_sub_query @
 5969        query(QueryId, _, sub_query)
 5970        \
 5971        phase(QueryId, union),
 5972        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, OdbcParameters, FromParameters, _),
 5973        sub_query(QueryId, SubQuerySqlTokens, SubQuerySqlTail, SubQueryOdbcParameters)
 5974        <=>
 5975        TokensTail = SqlFromTokens,
 5976        FromTail = SqlRestrictionTokens,
 5977        SubQuerySqlTail = RestrictionTail,
 5978        SubQuerySqlTokens = SqlTokens,
 5979        append(OdbcParameters, FromParameters, SubQueryOdbcParameters).
 5980
 5981orphan_write_restriction @
 5982        check_query,
 5983        write_restriction(_, _, _, ApplicationValueLhs, Operator, ApplicationValueRhs),
 5984        original_cql(Cql)
 5985        <=>
 5986        throw(format('Unused restriction: ~w ~w ~w in CQL: ~w', [ApplicationValueLhs, Operator, ApplicationValueRhs, Cql])).
 5987
 5988% Ignore any join_on which comes for free in PostgreSQL
 5989% (if we do an UPDATE ... FROM) we get a free join to the target
 5990% NB: We can only get implicit_join/2 if dbms is PostgreSQL
 5991ignore_implicit_joins @
 5992        implicit_join(QueryId, Ignore, SubQueryId)
 5993        \
 5994        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB)
 5995        <=>
 5996        ( Ignore == TableAliasA ; Ignore == TableAliasB)
 5997        |
 5998        add_on(SubQueryId, TableAliasA-AttributeNameA==TableAliasB-AttributeNameB),
 5999        implicit_join_link(QueryId, SubQueryId).
 6000
 6001remove_duplicate_implicit_join_links @
 6002        implicit_join_link(QueryId, SubQueryId)
 6003        \
 6004        implicit_join_link(QueryId, SubQueryId)
 6005        <=>
 6006        true.
 6007
 6008recover_implicit_join_for_update @
 6009        implicit_join_sql(QueryId, Sql, Tail),
 6010        implicit_join_link(QueryId, SubQueryId),
 6011        on(SubQueryId, _, On)
 6012        <=>
 6013        sql_statement(SubQueryId, A, A, B, B, C, C, [], [], []),
 6014        write_join_ons(SubQueryId, On),
 6015        fetch_implicit_join_sql(SubQueryId, Sql, Tail).
 6016
 6017fetch_implicit_join_sql @
 6018        fetch_implicit_join_sql(SubQueryId, Sql, Tail),
 6019        sql_statement(SubQueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, _, _, _)
 6020        <=>
 6021        TokensTail = SqlFromTokens,
 6022        FromTail = SqlRestrictionTokens,
 6023        Tail = RestrictionTail,
 6024        Sql = SqlTokens.
 6025
 6026check_for_joins @
 6027        check_query,
 6028        join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB),
 6029        original_cql(Cql)
 6030        <=>
 6031        throw(format('Unused JOIN point ~w (check join operator present) in CQL: ~w',
 6032                     [join_on(TableAliasA, AttributeNameA, TableAliasB, AttributeNameB), Cql])).
 6033
 6034
 6035check_for_unused_select_bindings @
 6036        % Select bindings should have either been translated into select attributes (i.e. will appear in
 6037        % the SELECT clause) or been explicitly discarded.  Any left behind indicate a problem.
 6038        check_query,
 6039        select_binding(_, X, Attribute, _),
 6040        original_cql(Cql)
 6041        <=>
 6042        throw(format('Unused SELECT binding (missing GROUP BY?): ~n~w ~n~n~w~n~nin CQL: ~w', [X, Attribute, Cql])).
 6043
 6044
 6045check_for_unused_join_on_comparisons @
 6046        check_query,
 6047        write_join_ons(_, On),
 6048        original_cql(Cql)
 6049        <=>
 6050        throw(format('Unused join ON comparison <~w> in CQL: ~w', [On, Cql])).
 6051
 6052
 6053check_for_unused_comparisons @
 6054        check_query,
 6055        comparison(_, Lhs, ComparisonOperator, Rhs),
 6056        original_cql(Cql)
 6057        <=>
 6058        throw(format('Unused comparison: ~w ~w ~w in CQL: ~w', [Lhs, ComparisonOperator, Rhs, Cql])).
 6059
 6060
 6061cleanup_check_query @
 6062        check_query
 6063        <=>
 6064        true.
 6065
 6066
 6067odbc_state_change_statement_update @
 6068        prepare_odbc_statements,
 6069        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, SelectOdbcParameters, FromParameters, Outputs),
 6070        state_change_query(QueryId, StateChangeType, Schema, TableName)
 6071        <=>
 6072        dbms(Schema, 'Microsoft SQL Server'),
 6073        StateChangeType == update
 6074        |
 6075        TokensTail = SqlFromTokens,
 6076        FromTail = SqlRestrictionTokens,
 6077        RestrictionTail = [],
 6078        AllSqlTokens = SqlTokens,
 6079        append(SelectOdbcParameters, FromParameters, OdbcParameters),
 6080        create_cql_pre_state_change_select_sql(QueryId, StateChangeType, SqlFromTokens, TableName, OdbcParameters),
 6081        create_cql_state_change_statistics_sql(QueryId, StateChangeType, SqlFromTokens, TableName, OdbcParameters),
 6082        compile_tokens(AllSqlTokens, Sql),
 6083        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, TableName, Sql, OdbcParameters, Outputs).
 6084
 6085
 6086duplicate_from_clause @
 6087        copy_of_from(QueryId, Tokens, Tail, Parameters)
 6088        \
 6089        find_copy_of_from(QueryId, NewTokens, NewTail, NewParameters)
 6090        <=>
 6091        Parameters = NewParameters,
 6092        swap_tail(Tokens, Tail, NewTail, NewTokens).
 6093
 6094remove_cycles([], []):- !.
 6095remove_cycles([compile:_|As], [Bs]):- !, remove_cycles(As, Bs).
 6096remove_cycles([A|As], [A|Bs]):- !, remove_cycles(As, Bs).
 6097remove_cycles([_|As], Bs):- remove_cycles(As, Bs).
 6098
 6099odbc_state_change_statement_update_sqlite_1 @
 6100        update_table_alias(QueryId, _, _, TargetAlias)
 6101        \
 6102        prepare_odbc_statements,
 6103        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, SelectOdbcParameters, FromParameters, Outputs),
 6104        state_change_query(QueryId, StateChangeType, Schema, TableName)
 6105        <=>
 6106        dbms(Schema, 'SQLite'),
 6107        StateChangeType == update
 6108        |
 6109        TokensTail = [' WHERE rowid IN (SELECT ', TargetAlias, '.rowid '|SqlFromTokens],
 6110        FromTail = SqlRestrictionTokens,
 6111        AllSqlTokens = SqlTokens,
 6112        % Yikes. Initially I used copy_term here but the variables need to be shared (except the tail, of course)
 6113        swap_tail(SqlFromTokens, RestrictionTail, [], StateChangeSelectTokens),
 6114        swap_tail(SqlFromTokens, RestrictionTail, CopyFromTail, CopyFrom),
 6115        copy_of_from(QueryId, CopyFrom, CopyFromTail, FromParameters),
 6116        RestrictionTail = [')'],
 6117        append(SelectOdbcParameters, FromParameters, OdbcParameters),
 6118        create_cql_pre_state_change_select_sql(QueryId, StateChangeType, StateChangeSelectTokens, TableName, OdbcParameters),
 6119        create_cql_state_change_statistics_sql(QueryId, StateChangeType, StateChangeSelectTokens, TableName, OdbcParameters),
 6120        compile_tokens(AllSqlTokens, Sql),
 6121        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, TableName, Sql, OdbcParameters, Outputs).
 6122
 6123
 6124swap_tail(Var, RestrictionTail, Tail, Tail):-
 6125        RestrictionTail == Var, !.
 6126
 6127swap_tail([A|As], Tail, X, [A|Bs]):-
 6128        swap_tail(As, Tail, X, Bs).
 6129
 6130odbc_state_change_statement_update @
 6131        query_table_alias(QueryId, _, _, TableAlias),
 6132        update_table_alias(QueryId, _, _, TargetAlias)
 6133        \
 6134        prepare_odbc_statements,
 6135        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, SelectOdbcParameters, FromParameters, Outputs),
 6136        state_change_query(QueryId, StateChangeType, Schema, UpdateTableName)
 6137        <=>
 6138        dbms(Schema, 'PostgreSQL'),
 6139        implicit_join_sql(QueryId, ImplicitJoinSQL, [')'|ImplicitJoinTail]),
 6140        % If there is any query_table_alias which is NOT the same as the update_table_alias then the
 6141        % SqlRestrictionTokens will already contain a FROM
 6142        TableAlias \== TargetAlias,
 6143        StateChangeType == update
 6144        |
 6145        append(SelectOdbcParameters, FromParameters, OdbcParameters),
 6146        % This is full of nasty traps. We must build up two very similar but not identical queries. Take care not to instantiate too much before the copy_term/2!
 6147        RestrictionTail = [],
 6148        ImplicitJoinTail = SqlRestrictionTokens,
 6149        copy_term([' FROM '|SqlFromTokens]:FromTail, SqlPreFromTokens:[' INNER JOIN ', UpdateTableName, ' ', TargetAlias, ' ON ('|ImplicitJoinSQL]),
 6150        TokensTail = SqlFromTokens,
 6151        FromTail = SqlRestrictionTokens,
 6152        AllSqlTokens = SqlTokens,
 6153
 6154        create_cql_pre_state_change_select_sql(QueryId, StateChangeType, SqlPreFromTokens, UpdateTableName, OdbcParameters),
 6155        create_cql_state_change_statistics_sql(QueryId, StateChangeType, SqlPreFromTokens, UpdateTableName, OdbcParameters),
 6156        % Inject the implicit join here
 6157        % ImplicitJoin = [' INNER JOIN ', TableName, ' ', TableAlias, ' ON ', '(1=1)'],
 6158        compile_tokens(AllSqlTokens, Sql),
 6159        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, UpdateTableName, Sql, OdbcParameters, Outputs).
 6160
 6161
 6162odbc_state_change_statement_update @
 6163        query_table_alias(QueryId, _, TableName, TableAlias)
 6164        \
 6165        prepare_odbc_statements,
 6166        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, SelectOdbcParameters, FromParameters, Outputs),
 6167        state_change_query(QueryId, StateChangeType, Schema, TableName)
 6168        <=>
 6169        dbms(Schema, 'PostgreSQL'),
 6170        StateChangeType == update
 6171        |
 6172        append(SelectOdbcParameters, FromParameters, OdbcParameters),
 6173        % If there is no query_table_alias which is NOT the same as the update_table_alias then the
 6174        % SqlRestrictionTokens will NOT contain a FROM, so we must add one
 6175        TokensTail = SqlFromTokens,
 6176        FromTail = SqlRestrictionTokens,
 6177        RestrictionTail = [],
 6178        AllSqlTokens = SqlTokens,
 6179        % This case is much simpler than the above
 6180        create_cql_pre_state_change_select_sql(QueryId, StateChangeType, [' FROM ', TableName, ' ', TableAlias, ' '|SqlRestrictionTokens], TableName, OdbcParameters),
 6181        create_cql_state_change_statistics_sql(QueryId, StateChangeType, [' FROM ', TableName, ' ', TableAlias, ' '|SqlRestrictionTokens], TableName, OdbcParameters),
 6182        compile_tokens(AllSqlTokens, Sql),
 6183        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, TableName, Sql, OdbcParameters, Outputs).
 6184
 6185
 6186odbc_state_change_statement_not_update @
 6187        prepare_odbc_statements,
 6188        sql_statement(QueryId, SqlTokens, TokensTail, SqlFromTokens, FromTail, SqlRestrictionTokens, RestrictionTail, SelectOdbcParameters, FromParameters, Outputs),
 6189        state_change_query(QueryId, StateChangeType, Schema, TableName)
 6190        <=>
 6191        TokensTail = SqlFromTokens,
 6192        FromTail = SqlRestrictionTokens,
 6193        RestrictionTail = [],
 6194        AllSqlTokens = SqlTokens,
 6195        append(SelectOdbcParameters, FromParameters, OdbcParameters),
 6196        create_cql_pre_state_change_select_sql(QueryId, StateChangeType, SqlFromTokens, TableName, OdbcParameters),
 6197        ( StateChangeType == delete ->
 6198            create_cql_state_change_statistics_sql(QueryId, StateChangeType, SqlFromTokens, TableName, OdbcParameters)
 6199        ; otherwise->
 6200            true
 6201        ),
 6202        compile_tokens(AllSqlTokens, Sql),
 6203        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, TableName, Sql, OdbcParameters, Outputs).
 6204
 6205
 6206execute_state_change_query @
 6207        cql_statement_location(FileName, LineNumber)
 6208        \
 6209        cql_execute(OdbcCachingOption),
 6210        cql_odbc_state_change_statement(QueryId, StateChangeType, Schema, TableName, HalfCompiledSql, HalfCompiledOdbcParameters, _)
 6211        <=>
 6212        fully_compile_sql(HalfCompiledSql, HalfCompiledOdbcParameters, [], Sql, OdbcParameters, _),
 6213        get_transaction_context(TransactionId, _, AccessToken, _, Connection),
 6214        execute_on_connection(Schema,
 6215                              Connection,
 6216                              ( debug_before(Sql, Schema, OdbcParameters),
 6217                                identify_pre_state_change_values(QueryId, StateChangeType, Connection),
 6218                                cql_access_token_to_user_id(AccessToken, UserId),
 6219                                ( StateChangeType == insert,
 6220                                  statistic_monitored_attribute(Schema, TableName, _) ->
 6221                                    forall((statistic_monitored_attribute(Schema, TableName, MonitoredAttribute),
 6222                                            memberchk(odbc_parameter(Schema, TableName, MonitoredAttribute, ApplicationValue, insert_value, _), OdbcParameters)),
 6223                                           statistic_monitored_attribute_change(Schema, TableName, MonitoredAttribute, ApplicationValue, 1))
 6224                                ; otherwise ->
 6225                                    true
 6226                                ),
 6227                                odbc_data_types_and_inputs(OdbcParameters, OdbcDataTypes, OdbcInputs),
 6228                                log_state_change(Sql, StateChangeType, OdbcInputs),
 6229                                ( odbc_prepare_and_execute(OdbcCachingOption, Connection, FileName, LineNumber, Sql, OdbcDataTypes, OdbcInputs, Result)->
 6230                                    true
 6231                                ; otherwise->
 6232                                    % Some drivers may return SQL_NO_DATA_FOUND if an UPDATE or DELETE affects no rows. In fact,
 6233                                    % even Microsoft says they are supposed to do this:
 6234                                    % "If SQLExecute executes a searched update, insert, or delete statement that does not
 6235                                    %  affect any rows at the data source, the call to SQLExecute returns SQL_NO_DATA."
 6236                                    %   from http://msdn.microsoft.com/en-us/library/windows/desktop/ms713584(v=vs.85).aspx
 6237                                    Result = affected(0)
 6238                                ),
 6239                                ( Result = affected(N) ->
 6240                                    number_of_rows_affected(QueryId, Connection, N),
 6241                                    cql_log([], informational, 'CQL\t~w\t~w\t   ~w row(s) affected\t(~w:~w)', [UserId, TransactionId, N, FileName, LineNumber]),
 6242                                    ( N > 0 ->
 6243                                        identify_insert_row(StateChangeType, QueryId, Schema, TableName, Connection, Identity),
 6244                                        ( StateChangeType == insert->
 6245                                            DebugResult = identity(Identity)
 6246                                        ; otherwise->
 6247                                            DebugResult = Result
 6248                                        ),
 6249                                        identify_post_state_change_values(QueryId, Connection),
 6250                                        call_row_change_hooks(QueryId, Connection)
 6251                                    ; otherwise->
 6252                                        DebugResult = Result,
 6253                                        cleanup_cql_post_state_change_select_sql(QueryId)
 6254                                    )
 6255                                ; Result = row(Identity), dbms(Schema, 'PostgreSQL')->
 6256                                    postgres_identity(QueryId, Identity),
 6257                                    identify_insert_row(StateChangeType, QueryId, Schema, TableName, Connection, _),
 6258                                    number_of_rows_affected(QueryId, Connection, 1),
 6259                                    cql_log([], informational, 'CQL\t~w\t~w\t   Row inserted. Identity ~w\t(~w:~w)', [UserId, TransactionId, Identity, FileName, LineNumber]),
 6260                                    identify_post_state_change_values(QueryId, Connection),
 6261                                    call_row_change_hooks(QueryId, Connection),
 6262                                    DebugResult = identity(Identity)
 6263                                ),
 6264                                debug_after(exit, DebugResult))).
 6265
 6266
 6267
 6268collect_external_variables @
 6269        phase(QueryId, union),
 6270        sql_statement(QueryId, _, _, _, _, _, _, _, _, HalfCompiledOutputs)
 6271        ==>
 6272        strip_compile_instructions(HalfCompiledOutputs, Outputs),
 6273        union_outputs(QueryId, Outputs, []).
 6274
 6275strip_compile_instructions([], []):-!.
 6276strip_compile_instructions([_:Outputs|More], Result):-
 6277        !,
 6278        append(Outputs, O1, Result),
 6279        strip_compile_instructions(More, O1).
 6280strip_compile_instructions([Output|O1], [Output|O2]):-
 6281        strip_compile_instructions(O1, O2).
 6282
 6283
 6284collect_external_variables_1 @
 6285        conjunction_variable(_, ExternalVariable, ConjunctionVariable)
 6286        \
 6287        union_outputs(QueryId, [output(_, _, _, ConjunctionVariable)|Outputs], ExternalVariables)
 6288        <=>
 6289        union_outputs(QueryId, Outputs, [ExternalVariable|ExternalVariables]).
 6290
 6291
 6292do_not_create_a_union_if_there_is_an_order_by @
 6293        phase(QueryId, union),
 6294        order_bys(QueryId, _)
 6295        <=>
 6296        true.
 6297
 6298
 6299union_if_external_variables_the_same_and_there_is_no_order_by @
 6300        phase(QueryIdA, union)
 6301        \
 6302        sql_statement(QueryIdA, SqlTokensA, TokensTailA, SqlFromTokensA, FromTailA, SqlRestrictionTokensA, RestrictionTailA, SelectOdbcParametersA, FromOdbcParametersA, Outputs),
 6303        union_outputs(QueryIdA, [], ExternalVariables),
 6304        phase(QueryIdB, union),
 6305        sql_statement(QueryIdB, SqlTokensB, TokensTailB, SqlFromTokensB, FromTailB, SqlRestrictionTokensB, RestrictionTailB, SelectOdbcParametersB, FromOdbcParametersB, _),
 6306        union_outputs(QueryIdB, [], ExternalVariables)
 6307        <=>
 6308        append(SelectOdbcParametersA, SelectOdbcParametersB, SelectOdbcParameters),
 6309        append(FromOdbcParametersA, FromOdbcParametersB, FromOdbcParameters),
 6310        TokensTailA = SqlFromTokensA,
 6311        FromTailA = SqlRestrictionTokensA,
 6312        RestrictionTailA = [' UNION '|SqlTokensB],
 6313        TokensTailB = SqlFromTokensB,
 6314        FromTailB = SqlRestrictionTokensB,
 6315        RestrictionTailB = NewTail,
 6316        UnionSqlTokens = SqlTokensA,
 6317        sql_statement(QueryIdA, UnionSqlTokens, NewTail, A, A, B, B, SelectOdbcParameters, FromOdbcParameters, Outputs),
 6318        remove_query(QueryIdB, QueryIdA),
 6319
 6320        ( debugging(cql(union)) ->
 6321            prolog_load_context(source, FileName),
 6322            prolog_load_context(term_position, TermPosition),
 6323            stream_position_data(line_count, TermPosition, LineNumber),
 6324            debug(cql(union), 'UNION created ~w:~w~n', [FileName, LineNumber])
 6325        ;
 6326            true
 6327        ).
 6328
 6329
 6330join_has_no_on_clause @
 6331        check_for_unjoined_tables,
 6332        write_join(_,