View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Matt Lilley
    4    E-mail:        matt.s.lilley@gmail.com
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014, Mike Elston, Matt Lilley
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35/*  PostgreSQL is a trademark of the PostgreSQL Global Development Group.
   36    Microsoft, SQL Server, and Windows are either registered trademarks or
   37    trademarks of Microsoft Corporation in the United States and/or other
   38    countries. SQLite is a registered trademark of Hipp, Wyrick & Company,
   39    Inc in the United States. All other trademarks or registered trademarks
   40    are the property of their respective owners.
   41*/
   42
   43:-module(sql_write, [sql_write/3,
   44                     sql_quote_codes/3,
   45                     format_sql_error/3]).   46
   47:-use_module(library(cql/sql_keywords)).   48:-use_module(library(cql/sql_parser), [strip_sql_comments/2]).   49:-use_module(library(cql/cql), [cql_normalize_name/3]).   50
   51sql_write(Stream, Term, Options):-
   52        new_sql_stream(Output),
   53        sql_write_term(Term, '', Options, Output, Result),
   54        dump_sql_stream(Result, Stream).
   55
   56new_sql_stream(sql_stream(T, T, unknown, 0)).
   57dump_sql_stream(sql_stream(Tokens, [], _, _), Stream):-
   58        atomic_list_concat(Tokens, '', Atom),
   59        format(Stream, '~w', [Atom]).
   60
   61sql_emit_token(Format, Args, Class, Options, sql_stream(Tokens, Tail, OldClass, Indent), sql_stream(Tokens, NewTail, Class, NewIndent)):-
   62        memberchk(errors(html), Options),
   63        !,
   64        format(atom(T2), Format, Args),
   65        ( fail, Class == OldClass ->
   66            Tail = [T2|NewTail]
   67        ; otherwise->
   68            format(atom(T1), '<span class="~w">', [Class]),
   69            format(atom(T3), '</span>', []),
   70            Tail = [T1, T2, T3|NewTail]
   71        ),
   72        atomic_list_concat(Lines, '\n', T2),
   73        ( Lines = [SingleLine]->
   74            atom_length(SingleLine, Length),
   75            NewIndent is Indent + Length
   76        ; otherwise->
   77            append(_, [LastLine], Lines),
   78            atom_length(LastLine, NewIndent)
   79        ).
   80
   81sql_emit_token(Format, Args, _Class, _Options, sql_stream(Tokens, [Token|NewTail], Class, Indent), sql_stream(Tokens, NewTail, Class, NewIndent)):-
   82        format(atom(Token), Format, Args),
   83        atomic_list_concat(Lines, '\n', Token),
   84        ( Lines = [SingleLine]->
   85            atom_length(SingleLine, Length),
   86            NewIndent is Indent + Length
   87        ; otherwise->
   88            once(append(_, [LastLine], Lines)), % Apparently this is nondet!
   89            atom_length(LastLine, NewIndent)
   90        ).
   91
   92sql_append_raw_token(Token, sql_stream(Tokens, [Token|NewTail], Class,Indent), sql_stream(Tokens, NewTail, Class, Indent)).
   93
   94tab_stop(Stop, sql_stream(Tokens, Tail, Class, Indent), sql_stream(Tokens, Tail, Class, Indent)):-
   95        findall(32, between(1, Indent, _), Spaces),
   96        atom_codes(Stop, Spaces).
   97
   98
   99sql_write_term(Var, _, _)--> {var(Var), !, throw(var)}.
  100sql_write_term(Comments:Term, Indent, Options)--> !,
  101        sql_write_comments(Comments, Indent, Options),
  102        sql_write_term(Term, Indent, Options),
  103        sql_end_comment(Comments, Indent, Options).
  104
  105sql_write_term(table_definition(Name, Columns), Indent, Options)--> !,
  106        sql_emit_token('CREATE TABLE ', [], keyword, Options),
  107        !,
  108        sql_write_term(Name, Indent, Options),
  109        ( {Columns == {all}} ->
  110            {true}
  111        ; {otherwise}->
  112            sql_emit_token('(', [], punctuation, Options),
  113            sql_write_list_with_newlines(Columns, Indent, Options),
  114            sql_emit_token(')', [], punctuation, Options)
  115        ).
  116
  117sql_write_term(domain_definition(Name, Type), Indent, Options)--> !,
  118        sql_emit_token('CREATE DOMAIN ', [], keyword, Options),
  119        !,
  120        sql_write_term(Name, Indent, Options),
  121        sql_emit_token(' AS ', [], keyword, Options),
  122        sql_write_type(Type, Indent, Options).
  123
  124
  125sql_write_term(view_definition(Name, Columns, Expression, With), Indent, Options)--> !,
  126        sql_emit_token('CREATE VIEW ', [], keyword, Options),
  127        !,
  128        sql_write_term(Name, Indent, Options),
  129        sql_write_term(With, Indent, Options),
  130        ( {Columns == {all}} ->
  131            {true}
  132        ; {otherwise}->
  133            sql_emit_token('(', [], punctuation, Options),
  134            sql_write_term(Columns, Indent, Options),
  135            sql_emit_token(')', [], punctuation, Options)
  136        ),
  137        sql_emit_token(' AS~n', [], keyword, Options),
  138        sql_write_term(Expression, Indent, Options).
  139
  140sql_write_term(parameter(I), _Indent, Options)--> !,
  141        ( {memberchk(parameter_bindings(Bindings), Options)}->
  142            {nth0(I, Bindings, Value)},
  143            ( {Value = parameter(Name)}->
  144                sql_emit_token('~w', [Name], parameter, Options)
  145            ; {otherwise}->
  146                sql_emit_token('~C', [Value], parameter, Options)
  147            )
  148        ; {otherwise}->
  149            sql_emit_token('?', [], punctuation, Options)
  150        ).
  151sql_write_term(table(Name), Indent, Options)--> !,
  152        ( {memberchk(errors(html), Options),
  153           strip_sql_comments(Name, identifier(_,RawName))}->
  154            {format(atom(Token), '<a href="/sql_explorer/~w">', [RawName])},
  155            sql_append_raw_token(Token),
  156            sql_write_term(Name, Indent, Options),
  157            sql_append_raw_token('</a>')
  158        ; {otherwise}->
  159            sql_write_term(Name, Indent, Options)
  160        ).
  161
  162sql_write_term(domain(Name), Indent, Options)--> !,
  163        sql_write_term(Name, Indent, Options).
  164
  165sql_write_term(derived_table(Derivation, Correlation, _Type), Indent, Options)--> !,
  166        sql_write_term(Derivation, Indent, Options),
  167        sql_emit_token(' AS ', [], keyword, Options),
  168        sql_write_term(Correlation, Indent, Options).
  169
  170
  171sql_write_term(identifier(Schema, Name), Indent, Options)--> !,
  172        ( {Schema == {no_schema}}->
  173            {true}
  174        ; {memberchk(dbms('PostgreSQL'), Options)}->
  175            % No schema for 'PostgreSQL'
  176            {true}
  177        ; {otherwise}->
  178            sql_write_term(Schema, Indent, Options),
  179            sql_emit_token('.', [], punctuation, Options)
  180        ),
  181        ( {memberchk(dbms('PostgreSQL'), Options)}->
  182            {strip_sql_comments(Name, NameNoComments),
  183             cql_normalize_name('PostgreSQL', NameNoComments, Normalized)},
  184            sql_write_term(Normalized, Indent, Options)
  185        ; {otherwise}->
  186            sql_write_term(Name, Indent, Options)
  187        ).
  188
  189sql_write_term(schema(Catalog, Name), Indent, Options)--> !,
  190        ( {Catalog == {no_catalog}}->
  191            {true}
  192        ; {memberchk(dbms('PostgreSQL'), Options)}->
  193            % No catalog for 'PostgreSQL' either
  194            {true}
  195        ; {otherwise}->
  196            sql_write_term(Catalog, Indent, Options),
  197            sql_emit_token('.', [], punctuation, Options)
  198        ),
  199        sql_write_term(Name, Indent, Options).
  200
  201sql_write_term(literal(Value, decimal(_,_)), _Indent, Options)--> !,
  202        sql_emit_token('~w', [Value], literal, Options).
  203sql_write_term(literal(Value, string), _Indent, Options)--> !,
  204        sql_emit_token('\'', [], literal, Options),
  205        sql_write_literal(Value, Options),
  206        sql_emit_token('\'', [], literal, Options).
  207sql_write_term(literal(Value, identifier), _Indent, Options)--> !,
  208        ( {memberchk(dbms('PostgreSQL'), Options)},
  209          sql_emit_token('"', [], literal, Options),
  210          sql_write_literal(Value, Options),
  211          sql_emit_token('"', [], literal, Options)
  212        ; {otherwise}->
  213            sql_emit_token('[~q]', [Value], unknown, Options)
  214        ).
  215sql_write_term(literal(Value, int(_)), _Indent, Options)--> !,
  216        sql_emit_token('~q', [Value], literal, Options).
  217
  218sql_write_term(set_function(Functor, Quantifier, Arg), Indent, Options)--> !,
  219        ( {Functor = Comments:RealFunctor}->
  220            sql_write_comments(Comments, Indent, Options),
  221            {upcase_atom(RealFunctor, FunctorUC)},
  222            sql_write_term(FunctorUC, Indent, Options),
  223            sql_end_comment(Comments, Indent, Options)
  224        ; {otherwise}->
  225            {upcase_atom(Functor, FunctorUC)},
  226            sql_write_term(FunctorUC, Indent, Options)
  227        ),
  228        sql_emit_token('(', [], punctuation, Options),
  229        sql_write_term(Quantifier, Indent, Options),
  230        sql_write_term(Arg, Indent, Options),
  231        sql_emit_token(')', [], punctuation, Options).
  232
  233sql_write_term(count(all), _Indent, Options)--> !,
  234        sql_emit_token('COUNT', [], function, Options),
  235        sql_emit_token('(*)', [], punctuation, Options).
  236
  237sql_write_term(query(Query), Indent, Options)--> !,
  238        sql_write_term(Query, Indent, Options).
  239
  240sql_write_term({no_quantifier}, _, _)--> !.
  241sql_write_term({no_limit}, _, _)--> !.
  242sql_write_term(all, _, Options)--> !, sql_emit_token(' ALL ', [], operator, Options).
  243sql_write_term(distinct, _, Options)--> !, sql_emit_token(' DISTINCT ', [], keyword, Options).
  244
  245sql_write_term(update(Table, Set, From, Where), Indent, Options)--> !,
  246        sql_emit_token('UPDATE ', [], keyword, Options),
  247        sql_write_term(Table, Indent, Options),
  248        sql_emit_token('~n~wSET ', [Indent], keyword, Options),
  249        tab_stop(NewIndent),
  250        sql_write_list_with_newlines(Set, NewIndent, Options),
  251        sql_write_term(From, Indent, Options),
  252        sql_write_term(Where, Indent, Options).
  253
  254sql_write_term(delete(Table, Where), Indent, Options)--> !,
  255        sql_emit_token('DELETE FROM ', [], keyword, Options),
  256        sql_write_term(Table, Indent, Options),
  257        sql_write_term(Where, Indent, Options).
  258
  259
  260sql_write_term(insert(Table, Values), Indent, Options)--> !,
  261        sql_emit_token('INSERT INTO ', [], keyword, Options),
  262        sql_write_term(Table, Indent, Options),
  263        sql_emit_token(' ', [], keyword, Options),
  264        sql_write_term(Values, Indent, Options).
  265
  266sql_write_term(insert_source(Source, _Override, Target), Indent, Options)--> !,
  267        sql_emit_token('(', [], keyword, Options),
  268        sql_write_list_compact(Source, Indent, Options),
  269        sql_emit_token(') ', [], keyword, Options),
  270        sql_write_term(Target, Indent, Options).
  271
  272sql_write_term(values(List), Indent, Options)--> !,
  273        sql_emit_token('~n~wVALUES ', [Indent], keyword, Options),
  274        tab_stop(NewIndent),
  275        sql_write_list_with_newlines(List, NewIndent, Options).
  276
  277
  278sql_write_term(set(Target, Source), Indent, Options)--> !,
  279        sql_write_term(Target, Indent, Options),
  280        sql_emit_token(' = ', [], operator, Options),
  281        tab_stop(NewIndent),
  282        sql_write_term(Source, NewIndent, Options).
  283
  284sql_write_term(select(Quantifier, Selections, Source, Limit, {no_for}), Indent, Options)--> !,
  285        sql_emit_token('SELECT ', [], keyword, Options),
  286        sql_write_term(Quantifier, Indent, Options),
  287        ( {Selections = _:all}->
  288            sql_emit_token('*', [], punctuation, Options)
  289        ; {otherwise}->
  290            sql_write_list_with_newlines(Selections, Indent, [explicit_literals(true)|Options])
  291        ),
  292        sql_emit_token(' ', [], punctuation, Options),
  293        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
  294            sql_write_term(Limit, Indent, Options)
  295        ; {otherwise}->
  296            {true}
  297        ),
  298        sql_write_term(Source, Indent, Options),
  299        ( {memberchk(dbms('PostgreSQL'), Options),
  300           Limit \== {no_limit}}->
  301            sql_write_term(Limit, Indent, Options)
  302        ; {otherwise}->
  303            {true}
  304        ).
  305
  306sql_write_term(column(Name, Type, AllowsNulls, IsIdentity, _Default), Indent, Options)--> !,
  307        ( {memberchk(dbms(DBMS), Options)}->
  308            {cql_normalize_name(DBMS, Name, NormalizedName)}
  309        ; {otherwise}->
  310            {Name = NormalizedName}
  311        ),
  312        sql_emit_token('~w ', [NormalizedName], unknown, Options),
  313        ( {memberchk(dbms('PostgreSQL'), Options),
  314           IsIdentity == is_identity(true)} ->
  315            sql_emit_token(' SERIAL', [], keyword, Options)
  316        ; {Type = domain(Domain)} ->
  317            {format(atom(Token), '<a href="/sql_explorer/~w">', [Domain])},
  318            sql_append_raw_token(Token),
  319            sql_write_term(Type, Indent, Options),
  320            sql_append_raw_token('</a>')
  321        ; {otherwise}->
  322            sql_write_term(Type, Indent, Options)
  323        ),
  324        ( {IsIdentity == is_identity(true)}->
  325            sql_emit_token(' PRIMARY KEY', [], keyword, Options)
  326        ; {AllowsNulls == allows_nulls(true)}->
  327            {true}
  328        ; {otherwise}->
  329            sql_emit_token(' NOT NULL', [], keyword, Options)
  330        ).
  331
  332
  333sql_write_term(select(Quantifier, Selections, Source, Limit, For), Indent, Options)-->
  334        {memberchk(dbms('PostgreSQL'), Options),
  335        strip_sql_comments(For, for(ForClause)),
  336        strip_sql_comments(ForClause, xml_path(Separator)),
  337        strip_sql_comments(Selections, [derived_column(SingleItem, 'text()')])},
  338        !,
  339        sql_emit_token('array_to_string', [], function, Options),
  340        sql_emit_token('(', [], punctuation, Options),
  341        sql_emit_token('ARRAY', [], function, Options),
  342        sql_emit_token('(', [], punctuation, Options),
  343        sql_emit_token('SELECT ', [], keyword, Options),
  344        sql_write_term(Quantifier, Indent, Options),
  345        sql_write_term(SingleItem, Indent, Options),
  346        sql_emit_token(' ', [], punctuation, Options),
  347        sql_write_term(Source, Indent, Options),
  348        ( {Limit \== {no_limit}}->
  349            sql_write_term(Limit, Indent, Options)
  350        ; {otherwise}->
  351            {true}
  352        ),
  353        sql_emit_token(')', [], punctuation, Options),
  354        sql_emit_token(', ', [], comma, Options),
  355        sql_write_term(Separator, Indent, Options),
  356        sql_emit_token(')', [], punctuation, Options).
  357
  358sql_write_term(select(Quantifier, Selections, Source, Limit, For), Indent, Options)-->
  359        {memberchk(dbms('Microsoft SQL Server'), Options),
  360        strip_sql_comments(For, for(xml_path(Separator)))},
  361        !,
  362        sql_write_term(select(Quantifier, Selections, Source, Limit, {no_for}), Indent, Options),
  363        sql_emit_token('FOR XML PATH', [], keyword, Options),
  364        sql_emit_token('(', [], punctuation, Options),
  365        sql_write_term(Separator, Indent, Options),
  366        sql_emit_token(')', [], punctuation, Options).
  367
  368sql_write_term(routine(Name, Args), Indent, Options)--> !,
  369        sql_write_term(Name, Indent, Options),
  370        sql_emit_token('(', [], punctuation, Options),
  371        tab_stop(NewIndent),
  372        {sql_list_length(Args, L)},
  373        ( {L =:= 0} ->
  374            % Special case - routine argument lists may be empty. No other SQL lists may be
  375            {true}
  376        ; {L < 2}->
  377            sql_write_list_compact(Args, NewIndent, Options)
  378        ; {otherwise}->
  379            sql_write_list_with_newlines(Args, NewIndent, Options)
  380        ),
  381        sql_emit_token(')', [], punctuation, Options).
  382
  383
  384sql_write_term(top(percent(N)), Indent, Options)--> !,
  385        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
  386            sql_emit_token('TOP ', [], keyword, Options),
  387            sql_write_term(N, Indent, Options),
  388            sql_emit_token('PERCENT ', [], keyword, Options)
  389        ; {otherwise}->
  390            % Ignore TOP 100 PERCENT in 'PostgreSQL'
  391            {true}
  392        ).
  393
  394sql_write_term(top(N), Indent, Options)--> !,
  395        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
  396            sql_emit_token('TOP ', [], keyword, Options),
  397            sql_write_term(N, Indent, Options)
  398        ; {otherwise}->
  399            sql_emit_token('~n~wLIMIT ', [Indent], keyword, Options),
  400            sql_write_term(N, Indent, Options)
  401        ).
  402
  403sql_write_term(column(Qualifier, Name), Indent, Options)--> !,
  404        ( {Qualifier == {no_qualifier}}->
  405            {true}
  406        ; {otherwise}->
  407            sql_write_term(Qualifier, Indent, Options),
  408            sql_emit_token('.', [], punctuation, Options)
  409        ),
  410        sql_write_and_strip_comments(Name, Indent, Options, StrippedName, Comments),
  411        ( {reserved_sql_keyword(StrippedName)}->
  412            ( {memberchk(dbms('PostgreSQL'), Options)}->
  413                sql_emit_token('"', [], punctuation, Options),
  414                sql_write_term(StrippedName, Indent, Options),
  415                sql_emit_token('"', [], punctuation, Options)
  416            ; {otherwise}->
  417                sql_emit_token('[', [], punctuation, Options),
  418                sql_write_term(StrippedName, Indent, Options),
  419                sql_emit_token(']', [], punctuation, Options)
  420            )
  421        ; {otherwise}->
  422            sql_write_term(StrippedName, Indent, Options)
  423        ),
  424        sql_end_comments(Comments, Indent, Options).
  425
  426sql_write_term(group_expression(Expression, Collation), Indent, Options)--> !,
  427        sql_write_term(Expression, Indent, Options),
  428        ( {Collation == {no_collation}} ->
  429            {true}
  430        ; {otherwise}->
  431            sql_emit_token(' COLLATE ', [], keyword, Options),
  432            sql_write_term(Collation, Indent, Options)
  433        ).
  434
  435
  436sql_write_term(group_column(Name, Collation), Indent, Options)--> !,
  437        sql_write_term(Name, Indent, Options),
  438        ( {Collation == {no_collation}} ->
  439            {true}
  440        ; {otherwise}->
  441            sql_emit_token(' COLLATE ', [], keyword, Options),
  442            sql_write_term(Collation, Indent, Options)
  443        ).
  444
  445
  446sql_write_term(derived_column(Column, Alias), Indent, Options)--> !,
  447        ( {Alias \== {no_alias}}->
  448            sql_write_and_strip_comments(Column, Indent, Options, RawColumn, Comments1),
  449            ( {memberchk(dbms('PostgreSQL'), Options),
  450              RawColumn = column(_Qualifier, PossibleLiteral),
  451              strip_sql_comments(PossibleLiteral, literal(Literal, string))}->
  452                % If the DBMS is 'PostgreSQL' then when writing out something like
  453                %   SELECT 'foo' AS bar
  454                % we have to instead output
  455                %   SELECT 'foo'::text AS bar
  456                % if we want the type of bar to be well-defined. The same is probably true of numeric literals
  457                sql_emit_token('\'', [], punctuation, Options),
  458                sql_write_literal(Literal, Options),
  459                sql_emit_token('\'::text', [], punctuation, Options)
  460            ; {otherwise}->
  461                sql_write_term(RawColumn, Indent, Options)
  462            ),
  463            sql_end_comments(Comments1, Indent, Options),
  464            sql_emit_token(' AS ', [], keyword, Options),
  465            sql_write_and_strip_comments(Alias, Indent, Options, Identifier, Comments2),
  466            ( {atom(Identifier)} ->
  467                % Must quote any identifiers!
  468                sql_write_term(literal(Identifier, identifier), Indent, Options)
  469            ; {Identifier = literal(Value, string)}->
  470                sql_write_term(literal(Value, identifier), Indent, Options)
  471            ; {otherwise}->
  472                {throw(bad_column_alias(Identifier))}
  473            ),
  474            sql_end_comments(Comments2, Indent, Options)
  475        ; {otherwise}->
  476            sql_write_term(Column, Indent, Options)
  477        ).
  478
  479sql_write_term(from(From), Indent, Options)--> !,
  480        sql_emit_token('~n~wFROM ', [Indent], keyword, Options),
  481        sql_write_list_with_newlines(From, Indent, Options).
  482
  483/* Matt-style joins
  484sql_write_term(join(LHS, RHS), Indent, Options)-->!,
  485        tab_stop(NewIndent),
  486        sql_write_term(LHS, Indent, Options),
  487        sql_emit_token('~n~w', [NewIndent], punctuation, Options),
  488        sql_write_term(RHS, Indent, Options).
  489
  490sql_write_term(qualified_join(Type, RHS, On), Indent, Options)--> !,
  491        tab_stop(NewIndent),
  492        sql_emit_token('   ', [], punctuation, Options),
  493        sql_write_term(Type, Indent, Options),
  494        sql_emit_token('~n~w', [NewIndent], punctuation, Options),
  495        sql_write_term(RHS, Indent, Options),
  496        sql_write_term(On, Indent, Options).
  497
  498sql_write_term(cross_join(RHS), Indent, Options)--> !,
  499        tab_stop(NewIndent),
  500        sql_emit_token('  CROSS JOIN~n~w', [NewIndent], operator, Options),
  501        sql_write_term(RHS, Indent, Options).
  502*/
  503
  504/* Chris-style joins */
  505sql_write_term(join(LHS, RHS), Indent, Options)-->!,
  506        tab_stop(NewIndent),
  507        sql_write_term(LHS, Indent, Options),
  508        sql_emit_token('~n~w', [NewIndent], punctuation, Options),
  509        sql_write_term(RHS, Indent, Options).
  510
  511sql_write_term(qualified_join(Type, RHS, On), Indent, Options)--> !,
  512        tab_stop(NewIndent),
  513        sql_write_term(Type, Indent, Options),
  514        sql_emit_token(' ', [], punctuation, Options),
  515        sql_write_term(RHS, Indent, Options),
  516        sql_emit_token('~n  ~w', [NewIndent], punctuation, Options),
  517        sql_write_term(On, Indent, Options).
  518
  519sql_write_term(cross_join(RHS), Indent, Options)--> !,
  520        tab_stop(NewIndent),
  521        sql_emit_token('  CROSS JOIN~n~w', [NewIndent], operator, Options),
  522        sql_write_term(RHS, Indent, Options).
  523
  524
  525sql_write_term(correlation(Name, Columns), Indent, Options)-->!,
  526        sql_write_term(Name, Indent, Options),
  527        ( {Columns == {no_columns}}->
  528            {true}
  529        ; {otherwise}->
  530            sql_emit_token('(', [], punctuation, Options),
  531            sql_write_list_compact(Columns, Indent, Options),
  532            sql_emit_token(')', [], punctuation, Options)
  533        ).
  534
  535sql_write_term(correlated_table(Name, Correlation), Indent, Options)--> !,
  536        sql_write_term(Name, Indent, Options),
  537        ( {Correlation == {no_correlation}}->
  538            {true}
  539        ; {otherwise}->
  540            sql_emit_token(' AS ', [], keyword, Options),
  541            sql_write_term(Correlation, Indent, Options)
  542        ).
  543
  544sql_write_term(on(Condition), Indent, Options)--> !,
  545        sql_emit_token(' ON ', [], keyword, Options),
  546        sql_emit_token('(', [], punctuation, Options),
  547        sql_write_term(Condition, Indent, Options),
  548        sql_emit_token(')', [], punctuation, Options).
  549
  550sql_write_term(predicate(P), Indent, Options)--> !,
  551        sql_write_term(P, Indent, Options).
  552
  553sql_write_term(comparison(Op, LHS, RHS), Indent, Options)--> !,
  554        sql_write_term(LHS, Indent, Options),
  555        sql_emit_token(' ', [], punctuation, Options),
  556        sql_write_term(Op, Indent, Options),
  557        sql_emit_token(' ', [], punctuation, Options),
  558        sql_write_term(RHS, Indent, Options).
  559
  560sql_write_term(element(A), Indent, Options)--> !,
  561        sql_write_term(A, Indent, Options).
  562
  563sql_write_term(and(A, B), Indent, Options)-->
  564        {memberchk(suppress_collations, Options)},
  565        {should_suppress_collation(A)},
  566        !,
  567        sql_write_term(B, Indent, Options).
  568
  569sql_write_term(and(A, B), Indent, Options)-->
  570        {memberchk(suppress_trivial_conditions, Options)},
  571        {should_suppress_condition(B)},
  572        !,
  573        sql_write_term(A, Indent, Options).
  574
  575
  576sql_write_term(and(A, B), Indent, Options)--> !,
  577        tab_stop(S),
  578        sql_write_term(A, Indent, Options),
  579        sql_emit_token(' AND~n~w', [S], operator, Options),
  580        sql_write_term(B, Indent, Options).
  581
  582sql_write_term(or(A, B), Indent, Options)--> !,
  583        sql_emit_token('(', [], punctuation, Options),
  584        sql_write_term(A, Indent, Options),
  585        sql_emit_token(') ', [], punctuation, Options),
  586        sql_emit_token('OR', [], operator, Options),
  587        sql_emit_token(' (', [], punctuation, Options),
  588        sql_write_term(B, Indent, Options),
  589        sql_emit_token(')', [], punctuation, Options).
  590
  591sql_write_term(multiply(A,B), Indent, Options)--> !,  % WARNING
  592        sql_write_term(A, Indent, Options),
  593        sql_emit_token(' * ', [], operator, Options),
  594        sql_write_term(B, Indent, Options).
  595
  596sql_write_term(add(A,B), Indent, Options)--> !,  % WARNING
  597        sql_write_term(A, Indent, Options),
  598        sql_emit_token(' + ', [], operator, Options),
  599        sql_write_term(B, Indent, Options).
  600
  601sql_write_term(subtract(A,B), Indent, Options)--> !,  % WARNING
  602        sql_write_term(A, Indent, Options),
  603        sql_emit_token(' - ', [], operator, Options),
  604        sql_write_term(B, Indent, Options).
  605
  606sql_write_term(divide(A,B), Indent, Options)--> !,  % WARNING
  607        sql_write_term(A, Indent, Options),
  608        sql_emit_token(' / ', [], operator, Options),
  609        sql_write_term(B, Indent, Options).
  610
  611sql_write_term(not(X), Indent, Options)--> !,
  612        sql_emit_token('NOT', [], operator, Options),
  613        sql_emit_token(' (', [], punctuation, Options),
  614        sql_write_term(X, Indent, Options),
  615        sql_emit_token(')', [], punctuation, Options).
  616
  617sql_write_term(round(X, P), Indent, Options)--> !,
  618        sql_emit_token('ROUND', [], function, Options),
  619        sql_emit_token('(', [], punctuation, Options),
  620        sql_write_term(X, Indent, Options),
  621        sql_emit_token(',', [], comma, Options),
  622        sql_write_term(P, Indent, Options),
  623        sql_emit_token(')', [], punctuation, Options).
  624
  625sql_write_term(floor(X), Indent, Options)--> !,
  626        sql_emit_token('FLOOR', [], function, Options),
  627        sql_emit_token('(', [], punctuation, Options),
  628        sql_write_term(X, Indent, Options),
  629        sql_emit_token(')', [], punctuation, Options).
  630
  631sql_write_term(ceiling(X), Indent, Options)--> !,
  632        sql_emit_token('CEILING', [], function, Options),
  633        sql_emit_token('(', [], punctuation, Options),
  634        sql_write_term(X, Indent, Options),
  635        sql_emit_token(')', [], punctuation, Options).
  636
  637sql_write_term(float(X), Indent, Options)--> !,
  638        sql_emit_token('FLOAT', [], function, Options),
  639        sql_emit_token('(', [], punctuation, Options),
  640        sql_write_term(X, Indent, Options),
  641        sql_emit_token(')', [], punctuation, Options).
  642
  643sql_write_term(username(X), Indent, Options)--> !, % TBD: Force normalization
  644        sql_emit_token('USERNAME', [], function, Options),
  645        sql_emit_token('(', [], punctuation, Options),
  646        sql_write_term(X, Indent, Options),
  647        sql_emit_token(')', [], punctuation, Options).
  648
  649sql_write_term(permissions(X), Indent, Options)--> !, % TBD: Force normalization
  650        sql_emit_token('PERMISSIONS', [], function, Options),
  651        sql_emit_token('(', [], punctuation, Options),
  652        sql_write_term(X, Indent, Options),
  653        sql_emit_token(')', [], punctuation, Options).
  654
  655sql_write_term(getdate({}), _Indent, Options)-->
  656        ( {memberchk(dbms('PostgreSQL'), Options) ; memberchk(normalize, Options)}),
  657        !,
  658        sql_emit_token('CURRENT_TIMESTAMP', [], function, Options).
  659
  660sql_write_term(getdate({}), _Indent, Options)--> % TBD: Force normalization
  661        {memberchk(dbms('Microsoft SQL Server'), Options)},
  662        !,
  663        sql_emit_token('GETDATE', [], function, Options),
  664        sql_emit_token('()', [], punctuation, Options).
  665
  666sql_write_term(dbname({}), _Indent, Options)--> !, % TBD: Force normalization
  667        sql_emit_token('DBNAME', [], function, Options),
  668        sql_emit_token('()', [], punctuation, Options).
  669
  670sql_write_term(fn_now({}), _Indent, Options)-->
  671        ( {memberchk(dbms('PostgreSQL'), Options) ; memberchk(normalize, Options)}), !,
  672        sql_emit_token('CURRENT_TIMESTAMP', [], function, Options).
  673
  674sql_write_term(fn_now({}), _Indent, Options)--> !, % TBD: Force normalization
  675        sql_emit_token('{ fn now() }', [], legacy, Options).
  676
  677sql_write_term(len(X), Indent, Options)-->
  678        {memberchk(dbms('PostgreSQL'), Options)}, !,
  679        % The ANSI string-length function is called CHAR_LENGTH. This is, incredibly, unsupported by SQL Server
  680        sql_emit_token('CHAR_LENGTH', [], function, Options),
  681        sql_emit_token('(', [], punctuation, Options),
  682        sql_write_term(X, Indent, Options),
  683        sql_emit_token(')', [], punctuation, Options).
  684
  685sql_write_term(len(X), Indent, Options)--> !,
  686        sql_emit_token('LEN', [], function, Options),
  687        sql_emit_token('(', [], punctuation, Options),
  688        sql_write_term(X, Indent, Options),
  689        sql_emit_token(')', [], punctuation, Options).
  690
  691sql_write_term(str(X), Indent, Options)-->
  692        {memberchk(dbms('PostgreSQL'), Options)},
  693        !,
  694        % STR in SQL Server is used to convert floats to strings.
  695        % The default length is 9, and the default precision is 0
  696        % The 'PostgreSQL' equivalent is therefore like to_char(X, '9999999999')
  697        sql_emit_token('TO_CHAR', [], function, Options),
  698        sql_emit_token('(', [], punctuation, Options),
  699        sql_write_term(X, Indent, Options),
  700        sql_emit_token(', ', [], comma, Options),
  701        sql_emit_token('\'9999999999\'', [], literal, Options),
  702        sql_emit_token(')', [], punctuation, Options).
  703
  704sql_write_term(str(X), Indent, Options)--> !,
  705        sql_emit_token('STR', [], function, Options),
  706        sql_emit_token('(', [], punctuation, Options),
  707        sql_write_term(X, Indent, Options),
  708        sql_emit_token(')', [], punctuation, Options).
  709
  710sql_write_term(concatenate(A,B), Indent, Options)--> !,
  711        sql_write_term(A, Indent, Options),
  712        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
  713            sql_emit_token(' + ', [], punctuation, Options)
  714        ; {otherwise}->
  715            sql_emit_token(' || ', [], punctuation, Options)
  716        ),
  717        sql_write_term(B, Indent, Options).
  718
  719sql_write_term(add_interval(A,B), Indent, Options)--> !,
  720        sql_write_term(A, Indent, Options),
  721        sql_emit_token(' + ', [], punctuation, Options),
  722        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
  723            sql_write_term(B, Indent, Options)
  724        ; {otherwise}->
  725            sql_emit_token('CAST', [], function, Options),
  726            sql_emit_token('(', [], punctuation, Options),
  727            sql_write_term(B, Indent, Options),
  728            sql_emit_token(' || ', [], punctuation, Options),
  729            sql_emit_token(' \' days\'', [], literal, Options),
  730            sql_emit_token(' AS', [], keyword, Options),
  731            sql_emit_token(' interval', [], function, Options),
  732            sql_emit_token(')', [], punctuation, Options)
  733        ).
  734
  735sql_write_term(left(V, N), Indent, Options)--> !,
  736        sql_emit_token('LEFT', [], function, Options),
  737        sql_emit_token('(', [], punctuation, Options),
  738        sql_write_term(V, Indent, Options),
  739        sql_emit_token(', ', [], comma, Options),
  740        sql_write_term(N, Indent, Options),
  741        sql_emit_token(')', [], punctuation, Options).
  742
  743sql_write_term(right(V, N), Indent, Options)--> !,
  744        sql_emit_token('RIGHT', [], function, Options),
  745        sql_emit_token('(', [], punctuation, Options),
  746        sql_write_term(V, Indent, Options),
  747        sql_emit_token(', ', [], comma, Options),
  748        sql_write_term(N, Indent, Options),
  749        sql_emit_token(')', [], punctuation, Options).
  750
  751sql_write_term(rtrim(V), Indent, Options)--> !,
  752        sql_emit_token('RTRIM', [], function, Options),
  753        sql_emit_token('(', [], punctuation, Options),
  754        sql_write_term(V, Indent, Options),
  755        sql_emit_token(')', [], punctuation, Options).
  756
  757sql_write_term(ltrim(V), Indent, Options)--> !,
  758        sql_emit_token('LTRIM', [], function, Options),
  759        sql_emit_token('(', [], punctuation, Options),
  760        sql_write_term(V, Indent, Options),
  761        sql_emit_token(')', [], punctuation, Options).
  762
  763sql_write_term(upper(V), Indent, Options)--> !,
  764        sql_emit_token('UPPER', [], function, Options),
  765        sql_emit_token('(', [], punctuation, Options),
  766        sql_write_term(V, Indent, Options),
  767        sql_emit_token(')', [], punctuation, Options).
  768
  769sql_write_term(lower(V), Indent, Options)--> !,
  770        sql_emit_token('LOWER', [], function, Options),
  771        sql_emit_token('(', [], punctuation, Options),
  772        sql_write_term(V, Indent, Options),
  773        sql_emit_token(')', [], punctuation, Options).
  774
  775sql_write_term(day(A), Indent, Options)-->
  776        {memberchk(dbms('PostgreSQL'), Options)}, !,
  777        sql_emit_token('DATE_PART', [], function, Options),
  778        sql_emit_token('(', [], punctuation, Options),
  779        sql_emit_token('\'day\'', [], literal, Options),
  780        sql_emit_token(', ', [], comma, Options),
  781        sql_write_term(A, Indent, Options),
  782        sql_emit_token(')', [], punctuation, Options).
  783
  784sql_write_term(month(A), Indent, Options)-->
  785        {memberchk(dbms('PostgreSQL'), Options)}, !,
  786        sql_emit_token('DATE_PART', [], function, Options),
  787        sql_emit_token('(', [], punctuation, Options),
  788        sql_emit_token('\'month\'', [], literal, Options),
  789        sql_emit_token(', ', [], comma, Options),
  790        sql_write_term(A, Indent, Options),
  791        sql_emit_token(')', [], punctuation, Options).
  792
  793sql_write_term(year(A), Indent, Options)-->
  794        {memberchk(dbms('PostgreSQL'), Options)}, !,
  795        sql_emit_token('DATE_PART', [], function, Options),
  796        sql_emit_token('(', [], punctuation, Options),
  797        sql_emit_token('\'year\'', [], literal, Options),
  798        sql_emit_token(', ', [], comma, Options),
  799        sql_write_term(A, Indent, Options),
  800        sql_emit_token(')', [], punctuation, Options).
  801
  802sql_write_term(day(A), Indent, Options)--> !, % TBD: Force normalization
  803        sql_emit_token('DAY', [], function, Options),
  804        sql_emit_token('(', [], punctuation, Options),
  805        sql_write_term(A, Indent, Options),
  806        sql_emit_token(')', [], punctuation, Options).
  807
  808sql_write_term(month(A), Indent, Options)--> !, % TBD: Force normalization
  809        sql_emit_token('MONTH', [], function, Options),
  810        sql_emit_token('(', [], punctuation, Options),
  811        sql_write_term(A, Indent, Options),
  812        sql_emit_token(')', [], punctuation, Options).
  813
  814sql_write_term(year(A), Indent, Options)--> !, % TBD: Force normalization
  815        sql_emit_token('YEAR', [], function, Options),
  816        sql_emit_token('(', [], punctuation, Options),
  817        sql_write_term(A, Indent, Options),
  818        sql_emit_token(')', [], punctuation, Options).
  819
  820sql_write_term(dateadd(A,B,C), Indent, Options)-->
  821        {memberchk(dbms('PostgreSQL'), Options)}, !,
  822        sql_write_and_strip_comments(A, Indent, Options, Class, Comments),
  823        % Quirk. SQL Server allows implicit cast of 0 to a datetime to get 1/1/1901.
  824        sql_write_date(C, Indent, Options),
  825        sql_emit_token(' + ', [], punctuation, Options),
  826        sql_emit_token('CAST', [], function, Options),
  827        sql_emit_token('(', [], punctuation, Options),
  828        sql_emit_token('CAST', [], function, Options),
  829        sql_emit_token('(', [], punctuation, Options),
  830        sql_write_term(B, Indent, Options),
  831        sql_emit_token(' AS ', [], keyword, Options),
  832        sql_emit_token('text', [], function, Options),
  833        sql_emit_token(')', [], punctuation, Options),
  834        sql_emit_token(' || ', [], punctuation, Options),
  835        sql_emit_token('\' ~w\'', [Class], literal, Options),
  836        sql_emit_token(' AS ', [], keyword, Options),
  837        sql_emit_token('interval', [], function, Options),
  838        sql_emit_token(')', [], punctuation, Options),
  839        sql_end_comments(Comments, Indent, Options).
  840
  841sql_write_term(dateadd(A,B,C), Indent, Options)--> !, % TBD: Force normalization
  842        sql_emit_token('DATEADD', [], function, Options),
  843        sql_emit_token('(', [], punctuation, Options),
  844        sql_write_term(A, Indent, Options),
  845        sql_emit_token(', ', [], comma, Options),
  846        sql_write_term(B, Indent, Options),
  847        sql_emit_token(', ', [], comma, Options),
  848        sql_write_term(C, Indent, Options),
  849        sql_emit_token(')', [], punctuation, Options).
  850
  851sql_write_term(datepart(A,B), Indent, Options)-->
  852        ( {memberchk(dbms('PostgreSQL'), Options) ; memberchk(normalize, Options)}),
  853        !,
  854        sql_emit_token('EXTRACT', [], function, Options),
  855        sql_emit_token('(', [], punctuation, Options),
  856        sql_emit_token('\'', [], literal, Options),
  857        sql_write_term(A, Indent, Options),
  858        sql_emit_token('\'', [], literal, Options),
  859        sql_emit_token(' FROM ', [], keyword, Options),
  860        sql_write_term(B, Indent, Options),
  861        sql_emit_token(')', [], punctuation, Options).
  862
  863
  864sql_write_term(datepart(A,B), Indent, Options)--> !, % TBD: Force normalization
  865        sql_emit_token('EXTRACT', [], function, Options),
  866        sql_emit_token('(', [], punctuation, Options),
  867        sql_emit_token('\'', [], literal, Options),
  868        sql_write_term(A, Indent, Options),
  869        sql_emit_token('\'', [], literal, Options),
  870        sql_emit_token(', ', [], comma, Options),
  871        sql_write_term(B, Indent, Options),
  872        sql_emit_token(')', [], punctuation, Options).
  873
  874
  875sql_write_term(datename(A,B), Indent, Options)-->
  876        {memberchk(dbms('PostgreSQL'), Options)}, !, % Also Oracle
  877        sql_emit_token('TO_CHAR', [], function, Options),
  878        sql_emit_token('(', [], punctuation, Options),
  879        sql_write_term(B, Indent, Options),
  880        sql_emit_token(', ', [], comma, Options),
  881        sql_write_and_strip_comments(A, Indent, Options, AA, Comments),
  882        ( {normalize_date_type(AA, Type)}->
  883            {true}
  884        ; {otherwise}->
  885            {throw(cql_error(cannot_canonicalize_date_part, AA))}
  886        ),
  887        ( {Type == day_of_week} ->
  888            sql_emit_token('\'Day\'', [], literal, Options)
  889        ; {otherwise}->
  890            {throw(cql_error(cannot_map_date_type, Type))}
  891        ),
  892        sql_end_comments(Comments, Indent, Options),
  893        sql_emit_token(')', [], punctuation, Options).
  894
  895sql_write_term(datename(A,B), Indent, Options)--> !, % TBD: Force normalization
  896        sql_emit_token('DATENAME', [], function, Options),
  897        sql_emit_token('(', [], punctuation, Options),
  898        sql_write_term(A, Indent, Options),
  899        sql_emit_token(', ', [], comma, Options),
  900        sql_write_term(B, Indent, Options),
  901        sql_emit_token(')', [], punctuation, Options).
  902
  903sql_write_term(datediff(A,B,C), Indent, Options)-->
  904        {memberchk(dbms('PostgreSQL'), Options)}, !,
  905        sql_write_and_strip_comments(A, Indent, Options, AA, Comments),
  906        ( {normalize_date_type(AA, Type)}->
  907            {true}
  908        ; {otherwise}->
  909            {throw(cql_error(cannot_canonicalize_date_part, AA))}
  910        ),
  911        ( {Type == day}->
  912            sql_emit_token('DATE_PART', [], function, Options),
  913            sql_emit_token('(', [], punctuation, Options),
  914            sql_emit_token('\'day\'', [], literal, Options),
  915            sql_emit_token(', ', [], comma, Options),
  916            sql_write_date(C, Indent, Options),
  917            sql_emit_token(' - ', [], punctuation, Options),
  918            sql_write_date(B, Indent, Options),
  919            sql_emit_token(') ', [], punctuation, Options)
  920        ; {Type == week} ->
  921            sql_emit_token('TRUNC', [], function, Options),
  922            sql_emit_token('(', [], punctuation, Options),
  923            sql_emit_token('DATE_PART', [], function, Options),
  924            sql_emit_token('(', [], punctuation, Options),
  925            sql_emit_token('\'day\'', [], literal, Options),
  926            sql_emit_token(', ', [], comma, Options),
  927            sql_write_date(C, Indent, Options),
  928            sql_emit_token(' - ', [], punctuation, Options),
  929            sql_write_date(B, Indent, Options),
  930            sql_emit_token(')', [], punctuation, Options),
  931            sql_emit_token(' / ', [], punctuation, Options),
  932            sql_emit_token('7', [], literal, Options),
  933            sql_emit_token(')', [], punctuation, Options)
  934        ; {Type == second} ->
  935            % This is unfortunately quite complicated. Basically:
  936            % days_diff = DATE_PART('day', end - start)
  937            % hours_diff = days_diff * 24 + DATE_PART('hour', end - start )
  938            % minutes_diff = hours_diff * 60 + DATE_PART('minute', end - start )
  939            % seconds_diff = minutes_diff * 60 + DATE_PART('second', end - start )
  940            % So overall
  941            % ((DATE_PART('day', end - start) * 24 + DATE_PART('hour', end - start )) * 60 + DATE_PART('minute', end - start )) * 60 + DATE_PART('second', end - start )
  942
  943            sql_emit_token('(', [], punctuation, Options),
  944            sql_emit_token('(', [], punctuation, Options),
  945            sql_emit_token('DATE_PART', [], function, Options),
  946            sql_emit_token('(', [], punctuation, Options),
  947            sql_emit_token('\'day\'', [], literal, Options),
  948            sql_emit_token(', ', [], comma, Options),
  949            sql_write_term(C, Indent, Options),
  950            sql_emit_token(' - ', [], punctuation, Options),
  951            sql_write_term(B, Indent, Options),
  952            sql_emit_token(') ', [], punctuation, Options),
  953            sql_emit_token(' * ', [], punctuation, Options),
  954            sql_emit_token('24', [], literal, Options),
  955            sql_emit_token(' + ', [], punctuation, Options),
  956            sql_emit_token('DATE_PART', [], function, Options),
  957            sql_emit_token('(', [], punctuation, Options),
  958            sql_emit_token('\'hour\'', [], literal, Options),
  959            sql_emit_token(', ', [], comma, Options),
  960            sql_write_term(C, Indent, Options),
  961            sql_emit_token(' - ', [], punctuation, Options),
  962            sql_write_term(B, Indent, Options),
  963            sql_emit_token(')', [], punctuation, Options),
  964            sql_emit_token(')', [], punctuation, Options),
  965            sql_emit_token(' * ', [], punctuation, Options),
  966            sql_emit_token('60', [], literal, Options),
  967            sql_emit_token(' + ', [], punctuation, Options),
  968            sql_emit_token('DATE_PART', [], function, Options),
  969            sql_emit_token('(', [], punctuation, Options),
  970            sql_emit_token('\'minute\'', [], literal, Options),
  971            sql_emit_token(', ', [], comma, Options),
  972            sql_write_term(C, Indent, Options),
  973            sql_emit_token(' - ', [], punctuation, Options),
  974            sql_write_term(B, Indent, Options),
  975            sql_emit_token(')', [], punctuation, Options),
  976            sql_emit_token(')', [], punctuation, Options),
  977            sql_emit_token(' * ', [], punctuation, Options),
  978            sql_emit_token('60', [], literal, Options),
  979            sql_emit_token(' + ', [], punctuation, Options),
  980            sql_emit_token('DATE_PART', [], function, Options),
  981            sql_emit_token('(', [], punctuation, Options),
  982            sql_emit_token('\'second\'', [], literal, Options),
  983            sql_emit_token(', ', [], comma, Options),
  984            sql_write_term(C, Indent, Options),
  985            sql_emit_token(' - ', [], punctuation, Options),
  986            sql_write_term(B, Indent, Options),
  987            sql_emit_token(') ', [], punctuation, Options)
  988        ; {Type == year} ->
  989            sql_emit_token('DATE_PART', [], function, Options),
  990            sql_emit_token('(', [], punctuation, Options),
  991            sql_emit_token('\'year\'', [], literal, Options),
  992            sql_emit_token(', ', [], comma, Options),
  993            sql_write_date(C, Indent, Options),
  994            sql_emit_token(' - ', [], punctuation, Options),
  995            sql_write_date(B, Indent, Options),
  996            sql_emit_token(') ', [], punctuation, Options)
  997        ; {Type == month}->
  998            sql_emit_token('DATE_PART', [], function, Options),
  999            sql_emit_token('(', [], punctuation, Options),
 1000            sql_emit_token('\'year\'', [], literal, Options),
 1001            sql_emit_token(', ', [], comma, Options),
 1002            sql_write_date(C, Indent, Options),
 1003            sql_emit_token(' - ', [], punctuation, Options),
 1004            sql_write_date(B, Indent, Options),
 1005            sql_emit_token(') ', [], punctuation, Options),
 1006            sql_emit_token(' * ', [], punctuation, Options),
 1007            sql_emit_token('12', [], literal, Options),
 1008            sql_emit_token(' + ', [], punctuation, Options),
 1009            sql_emit_token('DATE_PART', [], function, Options),
 1010            sql_emit_token('(', [], punctuation, Options),
 1011            sql_emit_token('\'month\'', [], literal, Options),
 1012            sql_emit_token(', ', [], comma, Options),
 1013            sql_write_date(C, Indent, Options),
 1014            sql_emit_token(' - ', [], punctuation, Options),
 1015            sql_write_date(B, Indent, Options),
 1016            sql_emit_token(')', [], punctuation, Options)
 1017        ; {otherwise}->
 1018            {throw(cql_error(cannot_datediff, AA))}
 1019        ),
 1020        sql_end_comments(Comments, Indent, Options).
 1021
 1022sql_write_term(datediff(A,B,C), Indent, Options)--> !, % TBD: Force normalization
 1023        sql_emit_token('DATEDIFF', [], function, Options),
 1024        sql_emit_token('(', [], punctuation, Options),
 1025        sql_write_term(A, Indent, Options),
 1026        sql_emit_token(', ', [], comma, Options),
 1027        sql_write_term(B, Indent, Options),
 1028        sql_emit_token(', ', [], comma, Options),
 1029        sql_write_term(C, Indent, Options),
 1030        sql_emit_token(')', [], punctuation, Options).
 1031
 1032sql_write_term(replace(A,B,C), Indent, Options)--> !,
 1033        sql_emit_token('REPLACE', [], function, Options),
 1034        sql_emit_token('(', [], punctuation, Options),
 1035        sql_write_term(A, Indent, Options),
 1036        sql_emit_token(', ', [], comma, Options),
 1037        sql_write_term(B, Indent, Options),
 1038        sql_emit_token(', ', [], comma, Options),
 1039        sql_write_term(C, Indent, Options),
 1040        sql_emit_token(')', [], punctuation, Options).
 1041
 1042sql_write_term(substring(A,B,C), Indent, Options)--> !,
 1043        sql_emit_token('SUBSTRING', [], function, Options),
 1044        sql_emit_token('(', [], punctuation, Options),
 1045        sql_write_term(A, Indent, Options),
 1046        sql_emit_token(', ', [], comma, Options),
 1047        sql_write_term(B, Indent, Options),
 1048        sql_emit_token(', ', [], comma, Options),
 1049        sql_write_term(C, Indent, Options),
 1050        sql_emit_token(')', [], punctuation, Options).
 1051
 1052sql_write_term(charindex(ExpressionToFind, ExpressionToSearch, StartLocation), Indent, Options)-->
 1053        ( {memberchk(dbms('PostgreSQL'), Options) ; memberchk(normalize, Options)}),
 1054        !,
 1055        ( {strip_sql_comments(StartLocation, {no_start})}->
 1056            sql_emit_token('POSITION', [], function, Options),
 1057            sql_emit_token('(', [], punctuation, Options),
 1058            sql_write_term(ExpressionToFind, Indent, Options),
 1059            sql_emit_token(' IN ', [], keyword, Options),
 1060            sql_write_term(ExpressionToSearch, Indent, Options),
 1061            sql_emit_token(')', [], punctuation, Options)
 1062        ; {otherwise}->
 1063            sql_emit_token('POSITION', [], function, Options),
 1064            sql_emit_token('(', [], punctuation, Options),
 1065            sql_write_term(ExpressionToFind, Indent, Options),
 1066            sql_emit_token(' IN SUBSTRING', [], keyword, Options),
 1067            sql_emit_token('(', [], punctuation, Options),
 1068            sql_write_term(ExpressionToSearch, Indent, Options),
 1069            sql_emit_token(' FROM ', [], keyword, Options),
 1070            sql_write_term(StartLocation, Indent, Options),
 1071            sql_emit_token(')', [], punctuation, Options),
 1072            sql_emit_token(')', [], punctuation, Options)
 1073        ).
 1074
 1075sql_write_term(charindex(A,B,C), Indent, Options)--> !,
 1076        sql_emit_token('CHARINDEX', [], function, Options),
 1077        sql_emit_token('(', [], punctuation, Options),
 1078        sql_write_term(A, Indent, Options),
 1079        sql_emit_token(', ', [], comma, Options),
 1080        sql_write_term(B, Indent, Options),
 1081        ( {C == {no_start}} ->
 1082            {true}
 1083        ; {otherwise}->
 1084            sql_emit_token(', ', [], comma, Options),
 1085            sql_write_term(C, Indent, Options)
 1086        ),
 1087        sql_emit_token(')', [], punctuation, Options).
 1088
 1089sql_write_term(precision_cast(A,B,C), Indent, Options)--> !,
 1090        ( {memberchk(dbms('Microsoft SQL Server'), Options),
 1091           \+memberchk(normalize, Options)}->
 1092            sql_emit_token('CONVERT', [], function, Options),
 1093            sql_emit_token('(', [], punctuation, Options),
 1094            sql_write_term(A, Indent, Options),
 1095            sql_emit_token(', ', [], comma, Options),
 1096            sql_write_term(B, Indent, Options),
 1097            ( {C == {no_precision}} ->
 1098                {true}
 1099            ; {otherwise}->
 1100                sql_emit_token(', ', [], comma, Options),
 1101                sql_write_term(C, Indent, Options)
 1102            ),
 1103            sql_emit_token(')', [], punctuation, Options)
 1104        ; {otherwise}->
 1105            ( {C == {no_precision}} ->
 1106                sql_emit_token('CAST', [], function, Options),
 1107                sql_emit_token('(', [], punctuation, Options),
 1108                sql_write_term(B, Indent, Options),
 1109                sql_emit_token(' AS ', [], keyword, Options),
 1110                sql_write_term(A, Indent, Options)
 1111            ; {A = _:native_type(NativeType),
 1112              strip_sql_comments(NativeType, varchar(_))}->
 1113                sql_emit_token('CAST', [], function, Options),
 1114                sql_emit_token('(', [], punctuation, Options),
 1115                sql_write_term(B, Indent, Options),
 1116                sql_emit_token(' AS ', [], keyword, Options),
 1117                sql_emit_token('VARCHAR', [], keyword, Options),
 1118                sql_emit_token('(', [], punctuation, Options),
 1119                sql_write_term(C, Indent, Options),
 1120                sql_emit_token(')', [], punctuation, Options)
 1121            ; {otherwise}->
 1122                {throw(unnormalizable(precision_cast(A,C)))}
 1123            ),
 1124            sql_emit_token(')', [], punctuation, Options)
 1125        ).
 1126
 1127sql_write_term(cast(A, B), Indent, Options)--> !,
 1128        sql_emit_token('CAST', [], function, Options),
 1129        sql_emit_token('(', [], punctuation, Options),
 1130        sql_write_term(A, Indent, Options),
 1131        sql_emit_token(' AS ', [], keyword, Options),
 1132        sql_write_term(B, Indent, Options),
 1133        sql_emit_token(')', [], punctuation, Options).
 1134
 1135sql_write_term(native_type(A), Indent, Options)--> !,
 1136        sql_write_type(A, Indent, Options).
 1137
 1138sql_write_term(like(LHS,Pattern,Escape), Indent, Options)--> !,
 1139        sql_write_term(LHS, Indent, Options),
 1140        sql_emit_token(' LIKE ', [], operator, Options),
 1141        sql_write_term(Pattern, Indent, Options),
 1142        ( {Escape == {no_escape}}->
 1143            {true}
 1144          ; {otherwise}->
 1145            sql_emit_token(' ESCAPE ', [], keyword, Options),
 1146            sql_write_term(Escape, Indent, Options)
 1147        ).
 1148
 1149sql_write_term(not_like(LHS,Pattern,Escape), Indent, Options)-->!,
 1150        sql_write_term(LHS, Indent, Options),
 1151        sql_emit_token(' NOT LIKE ', [], operator, Options),
 1152        sql_write_term(Pattern, Indent, Options),
 1153        ( {Escape == {no_escape}}->
 1154            {true}
 1155        ; {otherwise}->
 1156            sql_emit_token(' ESCAPE ', [], keyword, Options),
 1157            sql_write_term(Escape, Indent, Options)
 1158        ).
 1159
 1160sql_write_term({no_from}, _, _)--> !.
 1161sql_write_term({no_where}, _, _)--> !.
 1162sql_write_term({no_groupby}, _, _)--> !.
 1163sql_write_term({no_orderby}, _, _)--> !.
 1164sql_write_term({no_having}, _, _)--> !.
 1165sql_write_term({default_values}, _Indent, Options)--> !,
 1166        sql_emit_token(' DEFAULT VALUES ', [], keyword, Options).
 1167
 1168sql_write_term(source(From, Where, GroupBy, OrderBy, Having), Indent, Options)--> !,
 1169        sql_write_term(From, Indent, Options),
 1170        sql_write_term(Where, Indent, Options),
 1171        sql_write_term(GroupBy, Indent, Options),
 1172        ( {memberchk(dbms('PostgreSQL'), Options)}->
 1173            sql_write_term(Having, Indent, Options),
 1174            sql_write_term(OrderBy, Indent, Options)
 1175        ; {otherwise}->
 1176            sql_write_term(OrderBy, Indent, Options),
 1177            sql_write_term(Having, Indent, Options)
 1178        ).
 1179
 1180sql_write_term(exists(A), _Indent, Options)--> !,
 1181        sql_emit_token('EXISTS ', [], operator, Options),
 1182        tab_stop(S),
 1183        sql_write_term(A, S, Options).
 1184
 1185sql_write_term(cast(A,B), Indent, Options)--> !,
 1186        sql_emit_token('CAST', [], function, Options),
 1187        sql_emit_token('(', [], punctuation, Options),
 1188        sql_write_term(A, Indent, Options),
 1189        sql_emit_token(', ', [], comma, Options),
 1190        sql_write_term(B, Indent, Options),
 1191        sql_emit_token(')', [], punctuation, Options).
 1192
 1193sql_write_term(coalesce(List), Indent, Options)--> !,
 1194        sql_emit_token('COALESCE', [], function, Options),
 1195        sql_emit_token('(', [], punctuation, Options),
 1196        sql_write_list_compact(List, Indent, Options),
 1197        sql_emit_token(')', [], punctuation, Options).
 1198
 1199sql_write_term(isnull(A, B), Indent, Options)--> !,
 1200        ( {memberchk(dbms('Microsoft SQL Server'), Options),
 1201           \+memberchk(normalize, Options)}->
 1202            sql_emit_token('ISNULL', [], function, Options),
 1203            sql_emit_token('(', [], punctuation, Options),
 1204            sql_write_term(A, Indent, Options),
 1205            sql_emit_token(', ', [], comma, Options),
 1206            sql_write_term(B, Indent, Options),
 1207            sql_emit_token(')', [], punctuation, Options)
 1208        ; {otherwise}->
 1209            sql_emit_token('COALESCE', [], function, Options),
 1210            sql_emit_token('(', [], punctuation, Options),
 1211            sql_write_term(A, Indent, Options),
 1212            sql_emit_token(', ', [], comma, Options),
 1213            sql_write_term(B, Indent, Options),
 1214            sql_emit_token(')', [], punctuation, Options)
 1215        ).
 1216
 1217sql_write_term(negative(A), Indent, Options)--> !,
 1218        sql_emit_token('-', [], punctuation, Options), % WARNING: Order of operations
 1219        sql_write_term(A, Indent, Options).
 1220
 1221sql_write_term(abs(A), Indent, Options)--> !,
 1222        sql_emit_token('ABS', [], function, Options),
 1223        sql_emit_token('(', [], punctuation, Options),
 1224        sql_write_term(A, Indent, Options),
 1225        sql_emit_token(')', [], punctuation, Options).
 1226
 1227sql_write_term(else(Else), Indent, Options)--> !,
 1228        sql_write_term(Else, Indent, Options).
 1229
 1230sql_write_term(simple_case(Operand, Cases, Else), _Indent, Options)-->!,
 1231        tab_stop(S),
 1232        sql_emit_token('CASE ', [], keyword, Options),
 1233        tab_stop(SS),
 1234        sql_write_term(Operand, SS, Options),
 1235        sql_emit_token('~n~w', [SS], punctuation, Options),
 1236        sql_write_list_with_newlines_and_no_commas(Cases, SS, Options),
 1237        ( {Else == {no_else}}->
 1238            {true}
 1239        ; {otherwise}->
 1240            sql_emit_token('~n~w     ELSE ', [S], keyword, Options),
 1241            tab_stop(SSS),
 1242            sql_write_term(Else, SSS, Options)
 1243        ),
 1244        sql_emit_token('~n~wEND', [S], keyword, Options).
 1245
 1246sql_write_term(case(Cases, Else), _Indent, Options)-->!,
 1247        tab_stop(S),
 1248        sql_emit_token('CASE ', [], keyword, Options),
 1249        tab_stop(SS),
 1250        sql_write_list_with_newlines_and_no_commas(Cases, SS, Options),
 1251        ( {Else == {no_else}}->
 1252            {true}
 1253        ; {otherwise}->
 1254            sql_emit_token('~n~w     ELSE ', [S], keyword, Options),
 1255            tab_stop(SSS),
 1256            sql_write_term(Else, SSS, Options)
 1257        ),
 1258        sql_emit_token('~n~wEND', [S], keyword, Options).
 1259
 1260sql_write_term(when(searched(S), R), Indent, Options)--> !,
 1261        sql_emit_token('WHEN ', [], keyword, Options),
 1262        sql_write_term(S, Indent, Options),
 1263        sql_emit_token('~n~w  THEN ', [Indent], keyword, Options),
 1264        sql_write_term(R, Indent, Options).
 1265
 1266sql_write_term(when(Match, R), Indent, Options)--> !,
 1267        sql_emit_token('WHEN ', [], keyword, Options),
 1268        sql_write_term(Match, Indent, Options),
 1269        sql_emit_token('~n~w  THEN ', [Indent], keyword, Options),
 1270        sql_write_term(R, Indent, Options).
 1271
 1272sql_write_term(having(Having), Indent, Options)--> !,
 1273        sql_emit_token('~n~w', [Indent], punctuation, Options),
 1274        sql_emit_token('HAVING ', [], keyword, Options),
 1275        sql_write_term(Having, Indent, Options).
 1276
 1277sql_write_term(where(Where), Indent, Options)--> !,
 1278        sql_emit_token('~n~w', [Indent], punctuation, Options),
 1279        sql_emit_token('WHERE ', [], keyword, Options),
 1280        sql_write_term(Where, Indent, Options).
 1281
 1282sql_write_term(group_by(Groupings), Indent, Options)--> !,
 1283        sql_emit_token('~n~w', [Indent], punctuation, Options),
 1284        sql_emit_token('GROUP BY ', [], keyword, Options),
 1285        sql_write_list_with_newlines(Groupings, Indent, Options).
 1286
 1287sql_write_term(order_by(Orderings), Indent, Options)--> !,
 1288        sql_emit_token('~n~w', [Indent], punctuation, Options),
 1289        sql_emit_token('ORDER BY ', [], keyword, Options),
 1290        sql_write_list_with_newlines(Orderings, Indent, Options).
 1291
 1292sql_write_term(subquery(Q), _Indent, Options)--> !,
 1293        sql_emit_token('( ', [], punctuation, Options),
 1294        tab_stop(S),
 1295        sql_write_term(Q, S, Options),
 1296        sql_emit_token(')', [], punctuation, Options).
 1297
 1298sql_write_term(collate(C), Indent, Options)--> !,
 1299        sql_write_term(C, Indent, Options).
 1300
 1301sql_write_term(collation(C), Indent, Options)--> !,
 1302        sql_write_term(C, Indent, Options).
 1303
 1304sql_write_term(collated_factor(F, C), Indent, Options)-->
 1305        {memberchk(dbms('PostgreSQL'), Options) ; memberchk(suppress_collations, Options)},
 1306        !,
 1307        sql_write_term(F, Indent, Options),
 1308        sql_write_and_strip_comments(C, Indent, Options, _Collation, Comments),
 1309        sql_end_comments(Comments, Indent, Options).
 1310        % TBD: All collations for 'PostgreSQL' are just ignored.
 1311        %sql_write_term(Collation, Indent, Options).
 1312
 1313
 1314sql_write_term(collated_factor(F, C), Indent, Options)-->!,
 1315        sql_write_term(F, Indent, Options),
 1316        sql_emit_token(' COLLATE ', [], keyword, Options),
 1317        sql_write_term(C, Indent, Options).
 1318
 1319sql_write_term(sort_column(C), Indent, Options)--> !,
 1320        sql_write_term(C, Indent, Options).
 1321sql_write_term(index(I), Indent, Options)--> !, % Should we normalize this?
 1322        sql_write_term(I, Indent, Options).
 1323sql_write_term(sort_expression(Expression), Indent, Options)--> !,
 1324        sql_write_term(Expression, Indent, Options).
 1325
 1326
 1327sql_write_term(sort_key(Key, Collate, Order), Indent, Options)--> !,
 1328        sql_write_term(Key, Indent, Options),
 1329        ( {Collate == {no_collation}} ->
 1330            {true}
 1331        ; {otherwise}->
 1332            sql_emit_token(' COLLATE ', [], keyword, Options),
 1333            sql_write_term(Collate, Indent, Options)
 1334        ),
 1335        ( {Order == {no_order}} ->
 1336            ( {memberchk(normalize, Options)}->
 1337                sql_emit_token(' ASC ', [], keyword, Options)
 1338            ; {otherwise}->
 1339                {true}
 1340            )
 1341        ; {otherwise}->
 1342            sql_write_term(Order, Indent, Options)
 1343        ).
 1344
 1345sql_write_term(desc, _, Options)-->!, sql_emit_token(' DESC ', [], keyword, Options).
 1346sql_write_term(asc, _, Options)-->!, sql_emit_token(' ASC ', [], keyword, Options).
 1347
 1348sql_write_term(search(S), Indent, Options)--> !,
 1349        sql_write_term(S, Indent, Options).
 1350
 1351sql_write_term(in(Value, List), Indent, Options)--> !,
 1352        sql_write_term(Value, Indent, Options),
 1353        sql_emit_token(' IN ', [], operator, Options),
 1354        sql_write_term(List, Indent, Options).
 1355
 1356sql_write_term(not_in(Value, List), Indent, Options)--> !,
 1357        sql_write_term(Value, Indent, Options),
 1358        sql_emit_token(' NOT IN ', [], operator, Options),
 1359        sql_write_term(List, Indent, Options).
 1360
 1361sql_write_term(between(Value, Min, Max), Indent, Options)--> !,
 1362        sql_write_term(Value, Indent, Options),
 1363        sql_emit_token(' BETWEEN ', [], operator, Options),
 1364        sql_write_term(Min, Indent, Options),
 1365        sql_emit_token(' AND ', [], operator, Options),
 1366        sql_write_term(Max, Indent, Options).
 1367
 1368sql_write_term(list(Values), Indent, Options)--> !,
 1369        sql_emit_token('(', [], punctuation, Options),
 1370        sql_write_list_compact(Values, Indent, Options),
 1371        sql_emit_token(')', [], punctuation, Options).
 1372
 1373sql_write_term(join_type(Type), Indent, Options)--> !,
 1374        sql_write_term(Type, Indent, Options).
 1375
 1376sql_write_term(inner, _, Options)--> !,
 1377        sql_emit_token('INNER JOIN ', [], operator, Options).
 1378sql_write_term(outer(T1), Indent, Options)--> !,
 1379        sql_write_term(T1, Indent, Options),
 1380        sql_emit_token(' OUTER JOIN ', [], operator, Options).
 1381
 1382sql_write_term(left, _, Options)--> !, sql_emit_token('LEFT', [], operator, Options).
 1383sql_write_term(right, _, Options)--> !, sql_emit_token('RIGHT', [], operator, Options).
 1384sql_write_term(full, _, Options)--> !, sql_emit_token('FULL', [], operator, Options).
 1385
 1386sql_write_term(is_not_null(X), Indent, Options)--> !,
 1387        sql_write_term(X, Indent, Options),
 1388        sql_emit_token(' IS NOT NULL', [], operator, Options).
 1389
 1390sql_write_term(is_null(X), Indent, Options)--> !,
 1391        sql_write_term(X, Indent, Options),
 1392        sql_emit_token(' IS NULL', [], operator, Options).
 1393
 1394sql_write_term(union(LHS, RHS, Corresponding), Indent, Options)--> !,
 1395        ( {memberchk(unions(left), Options)}->
 1396            sql_emit_token('    ', [], punctuation, Options),
 1397            tab_stop(S),
 1398            sql_write_term(LHS, S, Options),
 1399            sql_emit_token('~n~wUNION~n~w', [Indent, Indent], keyword, Options),
 1400            ( {memberchk(unroll_unions(true), Options),
 1401              RHS = union(_, _)}->
 1402                sql_write_term(RHS, Indent, Options)
 1403            ; {otherwise}->
 1404                sql_emit_token('    ', [], punctuation, Options),
 1405                sql_write_term(RHS, S, Options)
 1406            )
 1407        ; {otherwise}->
 1408            tab_stop(S),
 1409            sql_write_term(LHS, Indent, Options),
 1410            sql_emit_token('~n~w  UNION~n~w', [S, S], keyword, Options),
 1411            sql_write_term(RHS, Indent, Options)
 1412        ),
 1413        ( {Corresponding == {no_corresponding}}->
 1414            {true}
 1415        ; {otherwise}->
 1416            sql_write_term(Corresponding, Indent, Options)
 1417        ).
 1418
 1419sql_write_term(union_all(LHS, RHS, Corresponding), Indent, Options)--> !,
 1420        tab_stop(S),
 1421        sql_write_term(LHS, Indent, Options),
 1422        sql_emit_token('~n~w  UNION', [S], keyword, Options),
 1423        sql_emit_token(' ALL~n~w', [S], operator, Options),
 1424        sql_write_term(RHS, Indent, Options),
 1425        ( {Corresponding == {no_corresponding}}->
 1426            {true}
 1427        ; {otherwise}->
 1428            sql_write_term(Corresponding, Indent, Options)
 1429        ).
 1430
 1431sql_write_term(except(LHS, RHS, Corresponding), Indent, Options)--> !,
 1432        tab_stop(S),
 1433        sql_write_term(LHS, Indent, Options),
 1434        sql_emit_token('~n~w  EXCEPT~n~w', [S, S], keyword, Options),
 1435        sql_write_term(RHS, Indent, Options),
 1436        ( {Corresponding == {no_corresponding}}->
 1437            {true}
 1438        ; {otherwise}->
 1439            sql_write_term(Corresponding, Indent, Options)
 1440        ).
 1441
 1442sql_write_term(except_all(LHS, RHS, Corresponding), Indent, Options)--> !,
 1443        tab_stop(S),
 1444        sql_write_term(LHS, Indent, Options),
 1445        sql_emit_token('~n~w  EXCEPT', [S], keyword, Options),
 1446        sql_emit_token(' ALL~n~w', [S], operator, Options),
 1447        sql_write_term(RHS, Indent, Options),
 1448        ( {Corresponding == {no_corresponding}}->
 1449            {true}
 1450        ; {otherwise}->
 1451            sql_write_term(Corresponding, Indent, Options)
 1452        ).
 1453
 1454sql_write_term({no_with}, _, _)--> !.
 1455sql_write_term(with(schemabinding), _, Options)--> !,
 1456        ( {memberchk(dbms('Microsoft SQL Server'), Options)}->
 1457            sql_emit_token(' WITH SCHEMABINDING', [], keyword, Options)
 1458        ; {otherwise}->
 1459            {true}
 1460        ).
 1461
 1462sql_write_term({null}, _Indent, Options)--> !,
 1463        sql_emit_token('NULL', [], null, Options).
 1464
 1465sql_write_term(join, _Indent, Options)--> !,
 1466        sql_emit_token('JOIN', [], keyword, Options).
 1467
 1468sql_write_term(Atom, _Indent, Options)-->
 1469        {atomic(Atom)}, !,
 1470        sql_emit_token('~w', [Atom], unknown, Options).
 1471
 1472sql_write_term({Foo}, _, _)-->
 1473        {throw(sql_write_curly(Foo))}.
 1474sql_write_term(Other, _, _)-->
 1475        {functor(Other, Functor, Arity),
 1476         throw(sql_write_term(Functor/Arity))}.
 1477
 1478sql_write_list_compact(Comments:List, Indent, Options)--> !,
 1479        sql_write_comments(Comments, Indent, Options),
 1480        sql_write_list_compact(List, Indent, Options),
 1481        sql_end_comment(Comments, Indent, Options).
 1482
 1483sql_write_list_compact([Tail], Indent, Options)--> !,
 1484        sql_write_term(Tail, Indent, Options).
 1485
 1486sql_write_list_compact([Head|Tail], Indent, Options)--> !,
 1487        sql_write_term(Head, Indent, Options),
 1488        sql_emit_token(', ', [], comma, Options),
 1489        sql_write_list_compact(Tail, Indent, Options).
 1490
 1491sql_write_list_with_newlines(Comments:List, Indent, Options)--> !,
 1492        sql_write_comments(Comments, Indent, Options),
 1493        sql_write_list_with_newlines(List, Indent, Options),
 1494        sql_end_comment(Comments, Indent, Options).
 1495
 1496sql_write_list_with_newlines(List, _ExistingIndent, Options)-->
 1497        tab_stop(S),
 1498        sql_write_list_with_newlines_1(List, S, Options).
 1499
 1500sql_write_list_with_newlines_1(Comments:List, Indent, Options)--> !,
 1501        sql_write_comments(Comments, Indent, Options),
 1502        sql_write_list_with_newlines(List, Indent, Options),
 1503        sql_end_comment(Comments, Indent, Options).
 1504
 1505sql_write_list_with_newlines_1([Tail], Indent, Options)--> !,
 1506        sql_write_term(Tail, Indent, Options).
 1507
 1508sql_write_list_with_newlines_1([Head|Tail], Indent, Options)--> !,
 1509        sql_write_term(Head, Indent, Options),
 1510        sql_emit_token(',~n~w', [Indent], comma, Options),
 1511        sql_write_list_with_newlines_1(Tail, Indent, Options).
 1512
 1513sql_write_list_with_newlines_and_no_commas(Comments:List, Indent, Options)--> !,
 1514        sql_write_comments(Comments, Indent, Options),
 1515        sql_write_list_with_newlines_and_no_commas(List, Indent, Options),
 1516        sql_end_comment(Comments, Indent, Options).
 1517
 1518sql_write_list_with_newlines_and_no_commas(List, _ExistingIndent, Options)-->
 1519        tab_stop(S),
 1520        sql_write_list_with_newlines_and_no_commas_1(List, S, Options).
 1521
 1522sql_write_list_with_newlines_and_no_commas_1(Comments:List, Indent, Options)--> !,
 1523        sql_write_comments(Comments, Indent, Options),
 1524        sql_write_list_with_newlines_and_no_commas(List, Indent, Options),
 1525        sql_end_comment(Comments, Indent, Options).
 1526
 1527sql_write_list_with_newlines_and_no_commas_1([Tail], Indent, Options)--> !,
 1528        sql_write_term(Tail, Indent, Options).
 1529
 1530sql_write_list_with_newlines_and_no_commas_1([Head|Tail], Indent, Options)--> !,
 1531        sql_write_term(Head, Indent, Options),
 1532        sql_emit_token('~n~w', [Indent], punctuation, Options),
 1533        sql_write_list_with_newlines_and_no_commas_1(Tail, Indent, Options).
 1534
 1535sql_write_and_strip_comments(Comments:Term, Indent, Options, X, [Comments|Y])-->
 1536        !,
 1537        sql_write_comments(Comments, Indent, Options),
 1538        sql_write_and_strip_comments(Term, Indent, Options, X, Y).
 1539
 1540sql_write_and_strip_comments(Term, _Indent, _Options, Term, [])--> [].
 1541
 1542
 1543sql_write_comments(meta(Comments, Errors), Indent, Options)--> !,
 1544        ( {Errors == {null}} ->
 1545            {true}
 1546        ; {memberchk(errors(ErrorMode), Options)}->
 1547            ( {ErrorMode == ansi} ->
 1548                sql_emit_token('~A', [[foreground-red]], machinery, Options)
 1549            ; {ErrorMode == html} ->
 1550                {format_sql_error(Errors, Index, Atom)},
 1551                ( {Index == {null}} ->
 1552                    {format(atom(Token), '<span class="error" title="~w">', [Atom])},
 1553                    sql_append_raw_token(Token)
 1554                ; {otherwise}->
 1555                    {format(atom(Token), '<span class="error error_~w" data-index="error_~w" title="~w" onMouseOver="mouseOver(event)" onMouseOut="mouseOut(event)" onClick="mouseClick(event)">', [Index, Index, Atom])},
 1556                    sql_append_raw_token(Token)
 1557                )
 1558            ; {otherwise}->
 1559                {true}
 1560            )
 1561        ; {otherwise}->
 1562            {true}
 1563        ),
 1564        sql_write_comments_1(Comments, Indent, Options).
 1565
 1566sql_write_comments_1([], _Indent, _Options)--> [].
 1567sql_write_comments_1([Comment|Comments], Indent, Options)-->
 1568        sql_write_comment(Comment, Indent, Options),
 1569        sql_write_comments_1(Comments, Indent, Options).
 1570
 1571format_sql_error(type_mismatch(I, A, B), I, Atom):-
 1572        !,
 1573        format(atom(Atom), 'Type mismatch between ~w and ~w', [A, B]).
 1574
 1575format_sql_error(order_by(top_level), {null}, 'ORDER BY is meaningless in the top level expression'):- !.
 1576format_sql_error(coalesce(null_argument), {null}, 'NULL as an argument to COALESCE() is meaningless'):- !.
 1577format_sql_error(order(having, order_by), {null}, 'HAVING clause should follow ORDER BY clause'):- !.
 1578format_sql_error(sql_escape, {null}, 'Escape from SQL with { fn ... }'):- !.
 1579format_sql_error(superfluous_quote(X), {null}, Message):- !, format(atom(Message), '~w does not require quoting here. It is quoted in the original source', [X]).
 1580format_sql_error(percent, {null}, 'PERCENT clause used, but has no effect in SQL2005 and greater').
 1581format_sql_error(for_clause, {null}, 'FOR clause?'):- !.
 1582format_sql_error(deprecated(D, R), {null}, Message):- !, format(atom(Message), 'Deprecated function ~w: Use ~w instead', [D, R]).
 1583format_sql_error(null_value, {null}, 'NULL is not actually allowed here. Use CAST(NULL AS <some type>)'):- !.
 1584
 1585format_sql_error(A, {null}, Atom):-
 1586        format(atom(Atom), 'Unknown error: ~q', [A]).
 1587
 1588sql_write_comment(comment(long, Codes), _Indent, Options)--> !,
 1589        sql_emit_token('/* ~s */ ', [Codes], comment, Options).
 1590
 1591sql_write_comment(comment(short, Codes), Indent, Options)--> !,
 1592        sql_emit_token('-- ~s~n~w', [Codes, Indent], comment, Options).
 1593
 1594sql_end_comments([], _Indent, _Options)--> !.
 1595sql_end_comments([Comment|Comments], Indent, Options)-->
 1596        sql_end_comment(Comment, Indent, Options),
 1597        sql_end_comments(Comments, Indent, Options).
 1598
 1599sql_end_comment(meta(_, Errors), _Indent, Options)--> !,
 1600        ( {Errors == {null}} ->
 1601            {true}
 1602        ; {memberchk(errors(ErrorMode), Options)}->
 1603            ( {ErrorMode == ansi} ->
 1604                {format(atom(Code), '~A', [{reset}])},
 1605                sql_append_raw_token(Code)
 1606            ; {ErrorMode == html} ->
 1607                sql_append_raw_token('</span>')
 1608            ; {otherwise}->
 1609                {true}
 1610            )
 1611        ; {otherwise}->
 1612            {true}
 1613        ).
 1614
 1615
 1616sql_write_type(Comments:Type, Indent, Options)--> !,
 1617        sql_write_comments(Comments, Indent, Options),
 1618        sql_write_type(Type, Indent, Options),
 1619        sql_end_comment(Comments, Indent, Options).
 1620
 1621sql_write_type(varchar(L), Indent, Options)--> !,
 1622        ( {L == {unknown}} ->
 1623            sql_emit_token('VARCHAR', [], keyword, Options)
 1624        ; {otherwise}->
 1625            sql_emit_token('VARCHAR', [], keyword, Options),
 1626            sql_emit_token('(', [], punctuation, Options),
 1627            sql_write_term(L, Indent, Options),
 1628            sql_emit_token(')', [], punctuation, Options)
 1629        ).
 1630
 1631sql_write_type(int, _Indent, Options)--> !,
 1632        sql_emit_token('INTEGER', [], keyword, Options).
 1633sql_write_type(smallint, _Indent, Options)--> !,
 1634        sql_emit_token('SMALLINT', [], keyword, Options).
 1635sql_write_type(tinyint, _Indent, Options)--> !,
 1636        ( {memberchk(dbms('PostgreSQL'), Options)}->
 1637            % 'PostgreSQL' does not have a TINYINT (which is 1 byte). Use SMALLINT (2 bytes) instead
 1638            sql_emit_token('SMALLINT', [], keyword, Options)
 1639        ; {otherwise}->
 1640            sql_emit_token('TINYINT', [], keyword, Options)
 1641        ).
 1642
 1643sql_write_type(decimal(Precision, Scale), Indent, Options)--> !,
 1644        sql_emit_token('DECIMAL', [], keyword, Options),
 1645        ( {Precision == {no_precision}} ->
 1646            {true}
 1647        ; {otherwise}->
 1648          sql_emit_token('(', [], punctuation, Options),
 1649          sql_write_term(Precision, Indent, Options),
 1650          ( {Scale == {no_scale}} ->
 1651              {true}
 1652          ; {otherwise}->
 1653              sql_emit_token(',', [], comma, Options),
 1654              sql_write_term(Scale, Indent, Options)
 1655          ),
 1656          sql_emit_token(')', [], punctuation, Options)
 1657        ).
 1658
 1659sql_write_type(float(Precision), Indent, Options)--> !,
 1660        ( {Precision == {no_precision}}->
 1661            sql_emit_token('FLOAT', [], keyword, Options)
 1662        ; {otherwise}->
 1663            sql_emit_token('FLOAT', [], keyword, Options),
 1664            sql_emit_token('(', [], punctuation, Options),
 1665            sql_write_term(Precision, Indent, Options),
 1666            sql_emit_token(')', [], punctuation, Options)
 1667        ).
 1668
 1669sql_write_type(real, _Indent, Options)--> !,
 1670        sql_emit_token('REAL', [], keyword, Options).
 1671
 1672sql_write_type(double(Precision), Indent, Options)--> !,
 1673        sql_emit_token('DOUBLE', [], keyword, Options),
 1674        sql_emit_token('(', [], punctuation, Options),
 1675        sql_write_term(Precision, Indent, Options),
 1676        sql_emit_token(')', [], punctuation, Options).
 1677
 1678sql_write_type(datetime, _Indent, Options)--> !, % Should normalize
 1679        ( {memberchk(dbms('PostgreSQL'), Options)}->
 1680            sql_emit_token('TIMESTAMP', [], keyword, Options)
 1681        ; {otherwise}->
 1682            sql_emit_token('DATETIME', [], keyword, Options)
 1683        ).
 1684
 1685sql_write_type(date, _Indent, Options)--> !, % Should normalize
 1686        sql_emit_token('DATE', [], keyword, Options).
 1687
 1688
 1689sql_list_length(_:X, Y):- !, sql_list_length(X, Y).
 1690sql_list_length([], 0):- !.
 1691sql_list_length([_A|B], N):-
 1692        sql_list_length(B, NN),
 1693        N is NN+1.
 1694
 1695normalize_date_type(day, day).
 1696normalize_date_type(dd, day).
 1697normalize_date_type(wk, week).
 1698normalize_date_type(week, week).
 1699normalize_date_type(second, second).
 1700normalize_date_type(weekday, day_of_week).
 1701normalize_date_type(year, year).
 1702normalize_date_type(month, month).
 1703
 1704sql_write_literal(Value, Options)-->
 1705        {atom_codes(Value, Codes),
 1706         sql_quote_codes(QuotedCodes, Codes, [])},
 1707        sql_emit_token('~s', [QuotedCodes], literal, Options).
 1708
 1709
 1710sql_quote_codes([], [], []):- !.
 1711sql_quote_codes([39, 39|Codes])-->
 1712        [39], !,
 1713        sql_quote_codes(Codes).
 1714sql_quote_codes([Code|Codes])-->
 1715        [Code],
 1716        sql_quote_codes(Codes).
 1717
 1718% Quirk. SQL Server allows implicit cast of 0 to a datetime to get 1/1/1901.
 1719sql_write_date(X, Indent, Options)-->
 1720        sql_write_and_strip_comments(X, Indent, Options, Date, Comments),
 1721        ( {Date == 0}->
 1722            sql_emit_token('CAST', [], function, Options),
 1723            sql_emit_token('(', [], punctuation, Options),
 1724            sql_emit_token('\'Jan 1 1901\' ', [], literal, Options),
 1725            sql_emit_token('AS timestamp without time zone', [], keyword, Options),
 1726            sql_emit_token(')', [], punctuation, Options)
 1727        ; {otherwise}->
 1728            sql_write_term(Date, Indent, Options)
 1729        ),
 1730        sql_end_comments(Comments, Indent, Options).
 1731
 1732should_suppress_collation(X):-
 1733        strip_sql_comments(X, predicate(comparison(_, Lhs, Rhs))),
 1734        ( Lhs = element(collated_factor(_, _))->
 1735            true
 1736        ; Rhs = element(collated_factor(_, _))->
 1737            true
 1738        ).
 1739
 1740should_suppress_condition(X):-
 1741        strip_sql_comments(X, predicate(comparison(_, element(1), element(1)))), !