1/*
2 *  Copyright (c) 2008, 2021, Oracle and/or its affiliates.
3 *
4 *  This program is free software; you can redistribute it and/or modify
5 *  it under the terms of the GNU General Public License, version 2.0,
6 *  as published by the Free Software Foundation.
7 *
8 *  This program is also distributed with certain software (including
9 *  but not limited to OpenSSL) that is licensed under separate terms,
10 *  as designated in a particular file or component or in included license
11 *  documentation.  The authors of MySQL hereby grant you an additional
12 *  permission to link the program and your derivative works with the
13 *  separately licensed software that they have included with MySQL.
14 *
15 *  This program is distributed in the hope that it will be useful,
16 *  but WITHOUT ANY WARRANTY; without even the implied warranty of
17 *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18 *  GNU General Public License, version 2.0, for more details.
19 *
20 *  You should have received a copy of the GNU General Public License
21 *  along with this program; if not, write to the Free Software
22 *  Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301  USA
23 */
24
25parser grammar MySQL51Parser;
26
27options {
28	output=AST;
29	tokenVocab=MySQL51Lexer;
30	superClass=MySQLParser;
31}
32
33import MySQL51Functions;
34
35tokens {
36SELECT;
37SELECT_EXPR;
38UNARY_MINUS;
39UNARY_PLUS;
40OPTIONS;
41FUNC;
42DIRECTION;
43ALIAS;
44FIELD;
45SUBSELECT;
46COMMA_JOIN;
47COLUMNS;
48INSERT_VALUES;
49INDEX_HINTS;
50ROLLBACK_POINT;	/* rollback to savepoint */
51/* token types for the various CREATE statements */
52CREATE_TABLE;
53/* helper tokens for column definitions  */
54NOT_NULL;
55DEFINITION;
56DEFINITIONS;
57COUNT_STAR;
58}
59
60@header{
61package com.mysql.clusterj.jdbc.antlr;
62}
63
64statement_list
65	:	stmts+=statement (SEMI stmts+=statement)* SEMI*
66		-> $stmts+
67	;
68
69statement
70	:	(	select
71		|	do_stmt
72		|	show_stmt
73		|	explain_stmt
74		|	insert
75		|	update
76		|	delete
77		|	transaction
78		|	create_table
79		|	COMMENT_RULE
80		)
81	;
82
83// $< DML
84
85do_stmt	:	DO exprList		-> ^(DO exprList)
86	;
87
88show_stmt
89  : (SHOW -> ^(SHOW))
90    ( AUTHORS     -> ^($show_stmt ^(AUTHORS))
91    | BINLOG EVENTS (IN logName=STRING)? (FROM NUMBER)? limit?  -> ^($show_stmt ^(BINLOG $logName? NUMBER? limit?))
92    | CHARACTER SET like_or_where?  -> ^($show_stmt ^(CHARACTER like_or_where?))
93    | COLLATION like_or_where?    -> ^($show_stmt ^(COLLATION like_or_where?))
94    | FULL? COLUMNS (FROM|IN) simple_table_ref_no_alias ((FROM|IN) ident)? like_or_where? -> ^($show_stmt ^(COLUMNS FULL? simple_table_ref_no_alias ident? like_or_where?))
95    | CONTRIBUTORS  -> ^($show_stmt ^(CONTRIBUTORS))
96    | CREATE DATABASE ident -> ^($show_stmt ^(CREATE DATABASE ident))
97    | CREATE EVENT ident    -> ^($show_stmt ^(CREATE EVENT ident))
98    | CREATE FUNCTION ident -> ^($show_stmt ^(CREATE FUNCTION ident))
99    | CREATE PROCEDURE ident  -> ^($show_stmt ^(CREATE PROCEDURE ident))
100    | CREATE TABLE simple_table_ref_no_alias  -> ^($show_stmt ^(CREATE TABLE simple_table_ref_no_alias))
101    | CREATE TRIGGER ident  -> ^($show_stmt ^(CREATE TRIGGER ident))
102    | CREATE VIEW ident   -> ^($show_stmt ^(CREATE VIEW ident))
103    | DATABASES like_or_where?  -> ^($show_stmt ^(DATABASES like_or_where?))
104    | ENGINE (INNODB | ident) (what=STATUS | what=MUTEX) // have to add INNODB token, because of SHOW INNODB STATUS :(
105                    -> ^($show_stmt ^(ENGINE INNODB? ident? $what))
106    | STORAGE? ENGINES    -> ^($show_stmt ^(ENGINES))
107    | ERRORS limit?     -> ^($show_stmt ^(ERRORS limit?))
108    | FULL? EVENTS      -> ^($show_stmt ^(EVENTS FULL?))
109    | FUNCTION CODE ident   -> ^($show_stmt ^(CODE FUNCTION ident))
110    | FUNCTION STATUS like_or_where?  -> ^($show_stmt ^(STATUS FUNCTION like_or_where?))
111    | GRANTS FOR
112        ( whom=USER_HOST
113        | whom=CURRENT_USER
114        | whom=CURRENT_USER LPAREN RPAREN
115        )         -> ^($show_stmt ^(GRANTS $whom))
116    | INDEX_SYM FROM simple_table_ref_no_alias ((FROM|IN) ident)? -> ^($show_stmt ^(INDEX_SYM simple_table_ref_no_alias ident?))
117    | INNODB STATUS   -> ^($show_stmt ^(ENGINE INNODB STATUS))
118    | OPEN TABLES ((FROM|IN) ident)? like_or_where? -> ^($show_stmt ^(OPEN ident? like_or_where?))
119    | PLUGINS     -> ^($show_stmt ^(PLUGINS))
120    | PROCEDURE CODE ident      -> ^($show_stmt ^(CODE PROCEDURE ident))
121    | PROCEDURE STATUS like_or_where? -> ^($show_stmt ^(STATUS PROCEDURE ident))
122    | PRIVILEGES      -> ^($show_stmt ^(PRIVILEGES))
123    | FULL? PROCESSLIST -> ^($show_stmt ^(PROCESSLIST FULL?))
124    | PROFILE show_profile_types (FOR QUERY NUMBER)? limit? -> ^($show_stmt ^(PROFILE show_profile_types NUMBER? limit?))
125    | PROFILES    -> ^($show_stmt ^(PROFILES))
126    | SCHEDULER STATUS  -> ^($show_stmt ^(STATUS SCHEDULER))
127    | optScopeModifier STATUS like_or_where?  -> ^($show_stmt ^(STATUS optScopeModifier? like_or_where?))
128    | TABLE STATUS ((FROM|IN) ident)? like_or_where?      -> ^($show_stmt  ^(STATUS TABLE ident? like_or_where?))
129    | TABLES ((FROM|IN) ident)? like_or_where?          -> ^($show_stmt ^(TABLES ident? like_or_where?))
130    | TRIGGERS ((FROM|IN) ident)? like_or_where?        -> ^($show_stmt ^(TRIGGERS ident? like_or_where?))
131    | optScopeModifier VARIABLES like_or_where?   -> ^($show_stmt ^(VARIABLES optScopeModifier? like_or_where?))
132    | WARNINGS limit?   -> ^($show_stmt ^(WARNINGS limit?))
133    )
134  ;
135
136optScopeModifier
137  : GLOBAL    -> GLOBAL
138  | SESSION   -> SESSION
139  | l=LOCAL   -> SESSION[$l]
140  | /* empty, defaults to SESSION */ -> SESSION
141  ;
142
143show_profile_types
144  : ALL
145  | BLOCK IO
146  | CONTEXT SWITCHES
147  | CPU
148  | IPC
149  | MEMORY
150  | PAGE FAULTS
151  | SOURCE
152  | SWAPS
153  ;
154
155like_or_where
156  : // behold, this is a special LIKE...does not allow expressions on the RHS
157    LIKE string_or_placeholder   -> ^(LIKE string_or_placeholder)
158  | WHERE expr    -> ^(WHERE expr)
159  ;
160
161explain_stmt
162  : EXPLAIN select -> ^(EXPLAIN select)
163  ;
164
165select
166@init {
167boolean seenUnion = false;
168}
169	:	select_paren
170		(UNION (mod=ALL | mod=DISTINCT)? union_selects+=select_paren {seenUnion=true;})*
171		 	-> {seenUnion}? ^(UNION $mod? select_paren $union_selects+)
172			-> select_paren
173	;
174
175select_paren
176	:	LPAREN select_paren RPAREN	-> select_paren
177	|	select_inner				-> select_inner
178	;
179
180select_inner
181	:	SELECT (options{k=1;}:select_options)*
182		exprs+=select_expr (COMMA exprs+=select_expr)*
183		(
184            (FROM table_references)
185            (WHERE where=where_condition)?
186            group_by?
187            (HAVING having=where_condition)?
188            order_by?
189            limit?
190            // these procedures are not "SQL-SPs" but C++ ones. very unlikely that we'll see them.
191            (PROCEDURE procId=ident procArgs=parenOptExprList)?
192            /* TODO: what is allowed in the "STRING" below? probably not N'foobar' etc. */
193            ((	INTO OUTFILE file=STRING opts=infile_options_helper
194                |	INTO DUMPFILE file=STRING
195                |	INTO vars+=variable (COMMA vars+=variable)*
196                )
197            )?
198            (forUpdate=FOR UPDATE | lock=LOCK IN SHARE MODE)?
199        |   order_by
200            limit?
201        |   limit
202		)?
203		-> ^(SELECT<com.mysql.clusterj.jdbc.antlr.node.SelectNode>
204				^(OPTIONS select_options*)?
205				^(COLUMNS $exprs+)
206				^(FROM table_references)?
207				^(WHERE<com.mysql.clusterj.jdbc.antlr.node.WhereNode> $where)?
208				group_by?
209				^(HAVING $having)?
210				order_by?
211				limit?
212				FOR?
213				LOCK?
214			)
215	;
216
217infile_options_helper
218	:	(	(COLUMNS|FIELDS)
219			(TERMINATED BY fieldTerm=STRING)?
220			(optEnclosed=OPTIONALLY? ENCLOSED BY fieldEncl=STRING)?			/* TODO: STRING here is one character, really */
221			(ESCAPED BY fieldEsc=STRING)?									/* TODO: STRING here is one character, really */
222		)?
223		(	LINES
224			(STARTING BY linesStart=STRING)?
225			(TERMINATED BY linesTerm=STRING)?
226		)?
227	;
228
229variable
230	:	SESSION_VARIABLE
231	|	GLOBAL_VARIABLE
232	;
233
234limit
235	:	LIMIT
236			(	((offset=number_or_placeholder COMMA)? lim=number_or_placeholder)
237			| 	(lim=number_or_placeholder offsetForm=OFFSET offset=number_or_placeholder)
238			)
239		-> ^(LIMIT $lim $offset? $offsetForm?)
240	;
241
242string_or_placeholder
243	:	STRING
244	|	VALUE_PLACEHOLDER
245	;
246
247number_or_placeholder
248	:	NUMBER
249	|	VALUE_PLACEHOLDER
250	;
251
252text_string
253	:	STRING
254	|	BINARY_VALUE
255	|	HEXA_VALUE
256	;
257
258group_by
259	:	GROUP BY
260			elements+=order_group_by_elements (COMMA elements+=order_group_by_elements )*
261		(rollup=WITH ROLLUP)?
262		-> ^(GROUP $elements+ $rollup?)
263	;
264
265order_by
266	:	ORDER BY
267			elements+=order_group_by_elements (COMMA elements+=order_group_by_elements )*
268		-> ^(ORDER $elements+)
269	;
270
271order_group_by_elements
272	:	expr
273		(	asc=ASC						-> ^(DIRECTION[$asc] expr)
274		|	desc=DESC					-> ^(DIRECTION[$desc] expr)
275		|	/* implicit ASC */			-> ^(DIRECTION["ASC"] expr)
276		)
277	;
278
279select_options
280	:	ALL
281	|	DISTINCT
282	|	DISTINCTROW
283	|	HIGH_PRIORITY
284	|	STRAIGHT_JOIN
285	|	SQL_SMALL_RESULT
286	|	SQL_BIG_RESULT
287// the following cause parser warnings
288//	|	SQL_BUFFER_RESULT
289//	|	SQL_CACHE
290//	|	SQL_NO_CACHE
291	|	SQL_CALC_FOUND_ROWS
292	;
293
294select_expr
295	:	expr (AS? ident)?		-> ^(SELECT_EXPR expr ^(ALIAS ident)?)
296	|	star=MULT				-> ^(SELECT_EXPR $star)
297	;
298/*	catch[RecognitionException re] {
299	   Object errorNode = (Object)adaptor.errorNode(input, retval.start, input.LT(-1), re);
300	   Object root_1 = (Object)adaptor.nil();
301     root_1 = (Object)adaptor.becomeRoot((Object)adaptor.create(SELECT_EXPR, "SELECT_EXPR"), root_1);
302     adaptor.addChild(root_1, errorNode);
303     adaptor.addChild(root_0, root_1);
304     retval.tree = (Object)adaptor.rulePostProcessing(root_0);
305	}
306*/
307table_references returns [int table_count]
308scope {
309int count;
310}
311@init {
312$table_references::count = 0;
313}
314@after {
315$table_references.table_count = $table_references::count;
316}
317	:	(	t1=table_ref 			-> $t1)
318		(	COMMA t2=table_ref		-> ^(COMMA_JOIN[$COMMA] $table_references $t2)
319		)*
320	;
321
322/* left factored to get rid of the recursion */
323table_ref
324	:	(t1=table_factor -> $t1 )
325		(
326			(LEFT|RIGHT)=>(ltype=LEFT|ltype=RIGHT) outer=OUTER? JOIN t3=table_ref lrjoinCond=join_condition_either
327				-> ^($ltype {$tree} $t3 $lrjoinCond $outer?)
328// join condition is not optional here
329		|	(type=INNER|type=CROSS)? JOIN t2=table_factor cond1=join_condition_either
330				-> ^(JOIN {$tree} $t2 $cond1? $type?)
331		|	(	type=STRAIGHT_JOIN t2=table_factor
332				(	(join_condition_on)=> cond2=join_condition_on	-> ^($type {$tree} $t2 $cond2)
333				|							-> ^($type {$tree} $t2)
334				)
335			)
336		|	(NATURAL)=> NATURAL ((type=LEFT|type=RIGHT) outer=OUTER?)? JOIN t2=table_factor -> ^(NATURAL $type? {$tree} $t2 $outer?)
337		)*
338	;
339
340table_factor
341	:	simple_table_ref_alias index_hint_list? {$table_references::count++;} -> ^(TABLE simple_table_ref_alias index_hint_list?)
342	|	LPAREN select_inner RPAREN AS? ident		{$table_references::count++;} -> ^(SUBSELECT select_inner ^(ALIAS ident))
343    |   LPAREN table_ref {$table_references::count++;} (COMMA table_ref {$table_references::count++;} )* RPAREN   -> ^(TABLE table_ref+)
344	/* ident in the following should really by 'OJ', but the parser accepts any identifier in its place */
345	|	LCURLY ident t1=table_ref LEFT OUTER JOIN t2=table_ref join_condition_on RCURLY
346			-> ^(ident $t1 $t2 join_condition_on)
347	|	DUAL								-> ^(DUAL)
348	;
349
350join_condition_on
351	:	ON where_condition		-> ^(ON where_condition)
352	;
353
354join_condition_either
355	:	join_condition_on
356	|	USING LPAREN fields+=ident (COMMA fields+=ident)* RPAREN		-> ^(USING $fields+)
357	;
358
359simple_table_ref_no_alias
360	:	first=ident (DOT second=ident)?		-> $first $second?
361	;
362
363simple_table_ref_alias
364	:	first=ident (DOT second=ident)? table_alias?		-> $first $second? table_alias?
365	;
366
367table_alias
368	:	AS? alias=ident	-> ^(ALIAS $alias)
369	;
370
371field_name
372@init {
373int i = 0;
374boolean seenStar = false;
375}
376	:	ident
377		({seenStar == false}?=>
378		  (DOT
379		    ({seenStar == false}? (ident | star=MULT {seenStar = true;}) {++i <= 2}?)
380		  )*
381		)
382		-> ^(FIELD ident+ $star?)
383//	|	(DOT)=>DOT column=field_name_column	-> ^(FIELD $column)
384	;
385
386/* list all keywords that can also be used as an identifier
387   This list is taken from the 5.1 YACC grammar
388*/
389
390ident
391	:
392	(	tok=ASCII
393	|	tok=BACKUP
394	|	tok=BEGIN
395	|	tok=BYTE
396	|	tok=CACHE
397	|	tok=CHARSET
398	|	tok=CHECKSUM
399	|	tok=CLOSE
400	|	tok=COMMENT
401	|	tok=COMMIT
402	|	tok=CONTAINS
403	|	tok=DEALLOCATE
404	|	tok=DO
405	|	tok=END
406	|	tok=EXECUTE
407	|	tok=FLUSH
408	|	tok=GROUP
409	|	tok=HANDLER
410	|	tok=HELP
411	|	tok=HOST
412	|	tok=INSTALL
413	|	tok=LABEL
414	|	tok=LANGUAGE
415	|	tok=NO
416	|	tok=OPEN
417	|	tok=OPTIONS
418	|	tok=OWNER
419	|	tok=PARSER
420	|	tok=PARTITION
421	|	tok=PORT
422	|	tok=PREPARE
423	|	tok=REMOVE
424	|	tok=REPAIR
425	|	tok=RESET
426	|	tok=RESTORE
427	|	tok=ROLLBACK
428	|	tok=SAVEPOINT
429	|	tok=SECURITY
430	|	tok=SERVER
431	|	tok=SIGNED
432	|	tok=SOCKET
433	|	tok=SLAVE
434	|	tok=SONAME
435	|	tok=START
436	|	tok=STOP
437	|	tok=TRUNCATE
438	|	tok=UNICODE
439	|	tok=UNINSTALL
440	|	tok=WRAPPER
441	|	tok=XA
442	|	tok=UPGRADE
443	)	-> ID[$tok]
444	|	ident_sp_label	-> {$ident_sp_label.tree}
445	;
446
447ident_sp_label
448	:
449	(	tok=ID!
450	|	tok=ACTION!
451	|	tok=ADDDATE!
452	|	tok=AFTER!
453	|	tok=AGAINST!
454	|	tok=AGGREGATE!
455	|	tok=ALGORITHM!
456	|	tok=ANY!
457	|	tok=AT!
458	|	tok=AUTHORS!
459	|	tok=AUTO_INCREMENT!
460	|	tok=AUTOEXTEND_SIZE!
461	|	tok=AVG_ROW_LENGTH!
462	|	tok=AVG!
463	|	tok=BINLOG!
464	|	tok=BIT!
465	|	tok=BLOCK!
466	|	tok=BOOL!
467	|	tok=BOOLEAN!
468	|	tok=BTREE!
469	|	tok=CASCADED!
470	|	tok=CHAIN!
471	|	tok=CHANGED!
472	|	tok=CIPHER!
473	|	tok=CLIENT!
474	|	tok=COALESCE!
475	|	tok=CODE!
476	|	tok=COLLATION!
477	|	tok=COLUMNS!
478	|	tok=FIELDS!
479	|	tok=COMMITTED!
480	|	tok=COMPACT!
481	|	tok=COMPLETION!
482	|	tok=COMPRESSED!
483	|	tok=CONCURRENT!
484	|	tok=CONNECTION!
485	|	tok=CONSISTENT!
486	|	tok=CONTEXT!
487	|	tok=CONTRIBUTORS!
488	|	tok=CPU!
489	|	tok=CUBE!
490	|	tok=DATA!
491	|	tok=DATAFILE!
492	|	tok=DATETIME!
493	|	tok=DATE!
494	|	tok=DAY!
495	|	tok=DEFINER!
496	|	tok=DELAY_KEY_WRITE!
497	|	tok=DES_KEY_FILE!
498	|	tok=DIRECTORY!
499	|	tok=DISABLE!
500	|	tok=DISCARD!
501	|	tok=DISK!
502	|	tok=DUMPFILE!
503	|	tok=DUPLICATE!
504	|	tok=DYNAMIC!
505	|	tok=ENDS!
506	|	tok=ENUM!
507	|	tok=ENGINE!
508	|	tok=ENGINES!
509	|	tok=ERRORS!
510	|	tok=ESCAPE!
511	|	tok=EVENT!
512	|	tok=EVENTS!
513	|	tok=EVERY!
514	|	tok=EXPANSION!
515	|	tok=EXTENDED!
516	|	tok=EXTENT_SIZE!
517	|	tok=FAULTS!
518	|	tok=FAST!
519	|	tok=FOUND!
520	|	tok=ENABLE!
521	|	tok=FULL!
522	|	tok=FILE!
523	|	tok=FIRST!
524	|	tok=FIXED!
525	|	tok=FRAC_SECOND!
526	|	tok=GEOMETRY!
527	|	tok=GEOMETRYCOLLECTION!
528	|	tok=GET_FORMAT!
529	|	tok=GRANTS!
530	|	tok=GLOBAL!
531	|	tok=HASH!
532	|	tok=HOSTS!
533	|	tok=HOUR!
534	|	tok=IDENTIFIED!
535	|	tok=INVOKER!
536	|	tok=IMPORT!
537	|	tok=INDEXES!
538	|	tok=INITIAL_SIZE!
539	|	tok=IO!
540	|	tok=IPC!
541	|	tok=ISOLATION!
542	|	tok=ISSUER!
543	|	tok=INNOBASE!
544	|	tok=INSERT_METHOD!
545	|	tok=KEY_BLOCK_SIZE!
546	|	tok=LAST!
547	|	tok=LEAVES!
548	|	tok=LESS!
549	|	tok=LEVEL!
550	|	tok=LINESTRING!
551	|	tok=LIST!
552	|	tok=LOCAL!
553	|	tok=LOCKS!
554	|	tok=LOGFILE!
555	|	tok=LOGS!
556	|	tok=MAX_ROWS!
557	|	tok=MASTER!
558	|	tok=MASTER_HOST!
559	|	tok=MASTER_PORT!
560	|	tok=MASTER_LOG_FILE!
561	|	tok=MASTER_LOG_POS!
562	|	tok=MASTER_USER!
563	|	tok=MASTER_PASSWORD!
564	|	tok=MASTER_SERVER_ID!
565	|	tok=MASTER_CONNECT_RETRY!
566	|	tok=MASTER_SSL!
567	|	tok=MASTER_SSL_CA!
568	|	tok=MASTER_SSL_CAPATH!
569	|	tok=MASTER_SSL_CERT!
570	|	tok=MASTER_SSL_CIPHER!
571	|	tok=MASTER_SSL_KEY!
572	|	tok=MAX_CONNECTIONS_PER_HOUR!
573	|	tok=MAX_QUERIES_PER_HOUR!
574	|	tok=MAX_SIZE!
575	|	tok=MAX_UPDATES_PER_HOUR!
576	|	tok=MAX_USER_CONNECTIONS!
577	|	tok=MAX_VALUE!
578	|	tok=MEDIUM!
579	|	tok=MEMORY!
580	|	tok=MERGE!
581	|	tok=MICROSECOND!
582	|	tok=MIGRATE!
583	|	tok=MINUTE!
584	|	tok=MIN_ROWS!
585	|	tok=MODIFY!
586	|	tok=MODE!
587	|	tok=MONTH!
588	|	tok=MULTILINESTRING!
589	|	tok=MULTIPOINT!
590	|	tok=MULTIPOLYGON!
591	|	tok=MUTEX!
592	|	tok=NAME!
593	|	tok=NAMES!
594	|	tok=NATIONAL!
595	|	tok=NCHAR!
596	|	tok=NDBCLUSTER!
597	|	tok=NEXT!
598	|	tok=NEW!
599	|	tok=NO_WAIT!
600	|	tok=NODEGROUP!
601	|	tok=NONE!
602	|	tok=NVARCHAR!
603	|	tok=OFFSET!
604	|	tok=OLD_PASSWORD!
605	|	tok=ONE_SHOT!
606	|	tok=ONE!
607	|	tok=PACK_KEYS!
608	|	tok=PAGE!
609	|	tok=PARTIAL!
610	|	tok=PARTITIONING!
611	|	tok=PARTITIONS!
612	|	tok=PASSWORD!
613	|	tok=PHASE!
614	|	tok=PLUGIN!
615	|	tok=PLUGINS!
616	|	tok=POINT!
617	|	tok=POLYGON!
618	|	tok=PRESERVE!
619	|	tok=PREV!
620	|	tok=PRIVILEGES!
621	|	tok=PROCESS!
622	|	tok=PROCESSLIST!
623	|	tok=PROFILE!
624	|	tok=PROFILES!
625	|	tok=QUARTER!
626	|	tok=QUERY!
627	|	tok=QUICK!
628	|	tok=REBUILD!
629	|	tok=RECOVER!
630	|	tok=REDO_BUFFER_SIZE!
631	|	tok=REDOFILE!
632	|	tok=REDUNDANT!
633	|	tok=RELAY_LOG_FILE!
634	|	tok=RELAY_LOG_POS!
635	|	tok=RELAY_THREAD!
636	|	tok=RELOAD!
637	|	tok=REORGANIZE!
638	|	tok=REPEATABLE!
639	|	tok=REPLICATION!
640	|	tok=RESOURCES!
641	|	tok=RESUME!
642	|	tok=RETURNS!
643	|	tok=ROLLUP!
644	|	tok=ROUTINE!
645	|	tok=ROWS!
646	|	tok=ROW_FORMAT!
647	|	tok=ROW!
648	|	tok=RTREE!
649	|	tok=SCHEDULE!
650	|	tok=SECOND!
651	|	tok=SERIAL!
652	|	tok=SERIALIZABLE!
653	|	tok=SESSION!
654	|	tok=SIMPLE!
655	|	tok=SHARE!
656	|	tok=SHUTDOWN!
657	|	tok=SNAPSHOT!
658	|	tok=SOUNDS!
659	|	tok=SOURCE!
660	|	tok=SQL_CACHE!
661	|	tok=SQL_BUFFER_RESULT!
662	|	tok=SQL_NO_CACHE!
663	|	tok=SQL_THREAD!
664	|	tok=STARTS!
665	|	tok=STATUS!
666	|	tok=STORAGE!
667	|	tok=STRING_KEYWORD!
668	|	tok=SUBDATE!
669	|	tok=SUBJECT!
670	|	tok=SUBPARTITION!
671	|	tok=SUBPARTITIONS!
672	|	tok=SUPER!
673	|	tok=SUSPEND!
674	|	tok=SWAPS!
675	|	tok=SWITCHES!
676	|	tok=TABLES!
677	|	tok=TABLESPACE!
678	|	tok=TEMPORARY!
679	|	tok=TEMPTABLE!
680	|	tok=TEXT!
681	|	tok=THAN!
682	|	tok=TRANSACTION!
683	|	tok=TRANSACTIONAL!
684	|	tok=TRIGGERS!
685	|	tok=TIMESTAMP!
686	|	tok=TIMESTAMP_ADD!
687	|	tok=TIMESTAMP_DIFF!
688	|	tok=TIME!
689	|	tok=TYPES!
690	|	tok=TYPE!
691	|	tok=UDF_RETURNS!
692	|	tok=FUNCTION!
693	|	tok=UNCOMMITTED!
694	|	tok=UNDEFINED!
695	|	tok=UNDO_BUFFER_SIZE!
696	|	tok=UNDOFILE!
697	|	tok=UNKNOWN!
698	|	tok=UNTIL!
699	|	tok=USER!
700	|	tok=USE_FRM!
701	|	tok=VARIABLES!
702	|	tok=VIEW!
703	|	tok=VALUE!
704	|	tok=WARNINGS!
705	|	tok=WAIT!
706	|	tok=WEEK!
707	|	tok=WORK!
708	|	tok=X509!
709	|	tok=YEAR!
710	)
711	{
712		adaptor.addChild(root_0, (Object)adaptor.create(ID, $tok));
713	}
714	;
715
716index_hint_list
717	:	index_hint (COMMA index_hint)*		-> ^(INDEX_HINTS index_hint+)
718	;
719
720index_hint
721scope {
722boolean namesOptional;
723}
724@init {
725$index_hint::namesOptional = false;
726}
727	:	USE {$index_hint::namesOptional = true;} index_hint_rest		-> ^(USE index_hint_rest)
728	|	IGNORE {$index_hint::namesOptional = false;} index_hint_rest	-> ^(IGNORE index_hint_rest)
729	|	FORCE {$index_hint::namesOptional = false;} index_hint_rest	-> ^(FORCE index_hint_rest)
730	;
731
732index_hint_rest
733	:	(name=INDEX|name=KEY) (FOR (usage=JOIN | usage=ORDER BY | usage=GROUP BY))?
734		LPAREN
735		( {$index_hint::namesOptional == true}?=> (names+=ident (COMMA names+=ident)*)?
736		| names+=ident (COMMA names+=ident)*
737		)
738		RPAREN
739		-> $name ^(LPAREN $names?) $usage?
740	;
741// $<Expressions
742
743exprList
744	:	e+=expr (COMMA e+=expr)*	-> $e+
745	;
746
747parenExpr
748	:	LPAREN expr RPAREN	-> ^(LPAREN<com.mysql.clusterj.jdbc.antlr.node.ParensNode> expr)
749	;
750
751parenExprList
752	:	LPAREN exprList RPAREN	-> ^(LPAREN exprList)
753	;
754
755parenOptExprList
756	:	LPAREN e+=exprList? RPAREN	-> ^(LPAREN $e*)
757	;
758
759expr
760	:	lhs=assignOrExpr (op=ASSIGN^ rhs=expr)?
761	;
762
763assignOrExpr
764	:	lhs=assignXORExpr ((op+=LOGICAL_OR^ | op+=OR<com.mysql.clusterj.jdbc.antlr.node.OrNode>^) rhs+=assignXORExpr)*
765	;
766
767assignXORExpr
768	:	lhs=assignAndExpr (op+=XOR^ rhs+=assignAndExpr)*
769	;
770
771assignAndExpr
772	:	lhs=assignNotExpr (( op+=LOGICAL_AND^ | op+=AND<com.mysql.clusterj.jdbc.antlr.node.AndNode>^ ) rhs+=assignNotExpr)*
773	;
774
775assignNotExpr
776	:	lhs=equalityExpr
777	|	op+=NOT<com.mysql.clusterj.jdbc.antlr.node.NotNode>^ rhs+=equalityExpr
778	;
779
780equalityExpr
781	:	bitwiseOrExpr
782		(op+=equalityOperator^ ((subselect_in_expr_rhs)=> subselect_in_expr_rhs | bitwiseOrExpr))*
783	;
784
785subselect_in_expr_rhs
786	:	(mod=ANY | mod=SOME | mod=ALL) LPAREN select RPAREN	-> ^(SUBSELECT $mod select)
787	;
788
789subselect
790	:	LPAREN select_inner RPAREN	-> ^(SUBSELECT select_inner)
791	;
792
793isOperator
794	:	IS NOT? (value2=NULL | value2=FALSE | value2=TRUE | value2=UNKNOWN)	-> ^(IS NOT? $value2)
795	;
796
797equalityOperator
798	:	(	value=EQUALS<com.mysql.clusterj.jdbc.antlr.node.EqualsNode>
799		|	value=NOT_EQUAL
800		|	value=LESS_THAN<com.mysql.clusterj.jdbc.antlr.node.LessThanNode>
801		|	value=LESS_THAN_EQUAL<com.mysql.clusterj.jdbc.antlr.node.LessEqualsNode>
802		|	value=GREATER_THAN<com.mysql.clusterj.jdbc.antlr.node.GreaterThanNode>
803		| 	value=GREATER_THAN_EQUAL<com.mysql.clusterj.jdbc.antlr.node.GreaterEqualsNode>
804		|	value=NULL_SAFE_NOT_EQUAL
805		| 	value=REGEXP
806		|	value=CASE
807		|	value=WHEN
808		|	value=THEN
809		|	value=ELSE
810		)
811	;
812
813bitwiseOrExpr
814    : lhs=bitwiseAndExpr
815    ( (op+=BITWISE_OR^ rhs+=bitwiseAndExpr)+
816// force compiler to always recognize NOT IN regardless of whatever follows
817    | (((NOT^)? IN^)=>(NOT^)? IN^ (parenExprList | subselect))
818    | LIKE^ unaryExpr (ESCAPE STRING)?  // STRING must be empty or one character long (or be "\\" if not in sql_mode NO_BACKSLASH_ESCAPES)
819    | isOperator^
820    | ((NOT^)? BETWEEN^)=> (NOT<com.mysql.clusterj.jdbc.antlr.node.NotNode>^)? (BETWEEN<com.mysql.clusterj.jdbc.antlr.node.BetweenNode>^ unaryExpr AND! unaryExpr )
821    )?
822    ;
823
824bitwiseAndExpr
825	:	lhs=shiftExpr (op+=BITWISE_AND^ rhs+=shiftExpr)*
826	;
827
828shiftExpr
829	:	lhs=additiveExpr ((op+=LEFT_SHIFT^ | op+=RIGHT_SHIFT^) rhs+=additiveExpr)*
830	;
831
832/* this is ugly because of INTERVAL:
833   As rightmost in an expression, it has the highest precendence.
834   Otherwise it must be followed by PLUS|MINUS.
835   TODO: It cannot be on the left of a MINUS, because that expression makes no sense.
836*/
837additiveExpr
838// force any PLUS or MINUS to be binary not unary for this rule
839    :   lhs=multiplicativeExpr ((PLUS|MINUS)=>(op+=PLUS^|op+=MINUS^) rhs+=multiplicativeExpr)*
840	;
841
842multOperator
843	:	value=MULT
844	|	value=DIVISION
845	|	value=DIV
846	|	value=MODULO
847	;
848
849multiplicativeExpr
850	:	lhs=bitwiseXORExpr (op+=multOperator^ rhs+=bitwiseXORExpr)*
851	;
852
853bitwiseXORExpr
854	:	lhs=unaryExpr (op+=BITWISE_XOR^ rhs+=unaryExpr)*
855	;
856
857unaryExpr
858	:	op=MINUS lhs=unaryExpr	-> ^(UNARY_MINUS[$op] $lhs)
859	|	op=PLUS lhs=unaryExpr	-> ^(UNARY_PLUS[$op] $lhs)
860	|	op=BITWISE_INVERSION lhs=unaryExpr -> ^(BITWISE_INVERSION $lhs)
861	|	lhsUnaryNot=unaryNotExpr	-> unaryNotExpr
862	;
863
864unaryNotExpr
865	:	op=NOT_OP lhs=unaryNotExpr	-> ^(NOT_OP $lhs)
866	|	lhsBin=binaryCollateExpr	-> binaryCollateExpr
867	;
868
869binaryCollateExpr
870	:	op=BINARY lhs=binaryCollateExpr		-> ^(BINARY $lhs)
871	|	op=COLLATE lhs=binaryCollateExpr	-> ^(COLLATE $lhs)
872	|	intervalExpr
873	;
874
875/* INTERVAL can bind extremely closely, if used as the rightmost subexpr of an expression, otherwise it is in additiveExpr
876   the validating predicate disallows its usage all by itself (can't select just an interval, it must be used in an additive expr)
877   defer checking that to a semantic tree phase.
878*/
879intervalExpr
880	:	(INTERVAL ~(LPAREN))=> INTERVAL expr timeUnit {input.LA(1) == PLUS || input.LA(1) == MINUS}? -> ^(INTERVAL expr timeUnit)
881	|	lhsPrim=primary	-> primary
882	;
883
884primary
885	:	lhsParen=parenExpr -> parenExpr
886	|	lhsLit=literal	-> literal
887	|	subselect	-> subselect
888	|	EXISTS subselect -> ^(EXISTS subselect)
889	// TODO: add missing primary expressions, like ROW, DEFAULT etc.
890	;
891
892literal
893	:	value=STRING
894	|	value=NUMBER
895	|	value=GLOBAL_VARIABLE
896	|	value=SESSION_VARIABLE
897	|	value=VALUE_PLACEHOLDER<com.mysql.clusterj.jdbc.antlr.node.PlaceholderNode>
898	|	value=BINARY_VALUE
899	|	value=HEXA_VALUE
900	|	value=NULL
901	|	value=TRUE
902	|	value=FALSE
903	|	(functionCall)=>functionCall
904	|	field_name
905	;
906// $>
907
908cast_data_type
909	:	BINARY (LPAREN NUMBER RPAREN)?
910	|	CHAR (LPAREN NUMBER RPAREN)?
911	|	DATE
912	|	DATETIME
913	|	TIME
914	|	DECIMAL	(LPAREN num1=NUMBER COMMA num2=NUMBER RPAREN)?
915	|	SIGNED INTEGER?
916	|	UNSIGNED INTEGER?
917	;
918
919timeUnit
920	:	MICROSECOND
921	|	SECOND
922	|	MINUTE
923	|	HOUR
924	|	DAY
925	|	WEEK
926	|	MONTH
927	|	QUARTER
928	|	YEAR
929	|	SECOND_MICROSECOND
930	|	MINUTE_MICROSECOND
931	|	MINUTE_SECOND
932	|	HOUR_MICROSECOND
933	|	HOUR_SECOND
934	|	HOUR_MINUTE
935	|	DAY_MICROSECOND
936	|	DAY_SECOND
937	|	DAY_MINUTE
938	|	DAY_HOUR
939	|	YEAR_MONTH
940	;
941
942/* TODO: add the SQL_TSI_ prefix versions */
943timestampUnit
944	:	FRAC_SECOND | MICROSECOND
945	|	SECOND
946	|	MINUTE
947	|	HOUR
948	|	DAY
949	|	WEEK
950	|	MONTH
951	|	QUARTER
952	|	YEAR
953	;
954
955where_condition
956	:	expr
957	;
958
959// $< Transactions
960
961/* generates bogus warning about RELEASE */
962transaction
963	// general trx statements
964	:	(	BEGIN  WORK?										-> ^(BEGIN WORK?)
965		|	START TRANSACTION (WITH CONSISTENT SNAPSHOT)?		-> ^(START SNAPSHOT?)
966		)
967	|	COMMIT WORK?
968		(AND NO? CHAIN)?
969		(NO? RELEASE)?											-> ^(COMMIT ^(CHAIN NO?)? ^(RELEASE NO?)?)
970	|	ROLLBACK WORK?
971		(AND NO? CHAIN)?
972		(NO? RELEASE)?											-> ^(ROLLBACK ^(CHAIN NO?)? ^(RELEASE NO?)?)
973	// NUMBER must be (0 | 1), no grammar checks done at this point, TODO check AUTOCOMMIT vs keywords/identifiers
974//	|	SET AUTOCOMMIT EQUALS NUMBER
975	|	SET
976		(	txnScope=GLOBAL
977		|	txnScope=SESSION
978		)?
979		TRANSACTION ISOLATION LEVEL
980		(	READ UNCOMMITTED			-> ^(ISOLATION UNCOMMITTED $txnScope)
981		|	READ COMMITTED				-> ^(ISOLATION COMMITTED $txnScope)
982		|	REPEATABLE READ				-> ^(ISOLATION REPEATABLE $txnScope)
983		|	SERIALIZABLE				-> ^(ISOLATION SERIALIZABLE $txnScope)
984		)
985	|	savepoint
986	|	lockTables
987	//	TODO support for XA transactions is missing
988	;
989
990// savepoint handling
991savepoint
992	:	RELEASE? SAVEPOINT ident				-> ^(SAVEPOINT ident RELEASE?)
993	|	ROLLBACK WORK? TO SAVEPOINT? ident		-> ^(ROLLBACK_POINT ident)
994	;
995
996// $> Transactions
997
998// $< Insert
999
1000insert
1001	:	INSERT (opt=LOW_PRIORITY | opt=DELAYED | opt=HIGH_PRIORITY)?
1002		IGNORE? INTO?
1003		table=simple_table_ref_no_alias
1004		(	insert_columns
1005		|	set_columns
1006		|	select
1007		)
1008		on_dup_key?
1009		-> ^(INSERT<com.mysql.clusterj.jdbc.antlr.node.InsertNode> IGNORE? INTO? $opt? ^(TABLE $table)
1010			/* the following three lines are really alts as they cannot appear at the same time */
1011			insert_columns?
1012			set_columns?
1013			select?
1014			on_dup_key?)
1015	;
1016
1017insert_columns
1018	:	(LPAREN column_name_list? RPAREN)?
1019		(VALUE|VALUES) LPAREN val+=insert_default_or_expression (COMMA val+=insert_default_or_expression)* RPAREN
1020			-> ^(INSERT_VALUES column_name_list? ^(VALUES[] $val+))
1021	;
1022
1023insert_default_or_expression
1024	:	DEFAULT
1025	|	expr
1026	;
1027
1028set_columns
1029	:	SET column_assignment (COMMA column_assignment)*	-> ^(SET column_assignment+)
1030	;
1031
1032on_dup_key
1033	:	ON DUPLICATE KEY UPDATE
1034		column_assignment (COMMA column_assignment)*	-> ^(DUPLICATE column_assignment+)
1035	;
1036
1037column_assignment
1038	:	field_name EQUALS
1039		(	DEFAULT			-> ^(EQUALS field_name DEFAULT)
1040		|	expr			-> ^(EQUALS field_name expr)
1041		)
1042	;
1043
1044column_name_list
1045	:	field_name (COMMA field_name)*	-> ^(COLUMNS field_name+)
1046	;
1047// $> Insert
1048
1049// $< Update
1050
1051update
1052	:	UPDATE LOW_PRIORITY? IGNORE?
1053		table=table_references			// this must be table_references because the mysql parser allows an alias here, even for single table updates (unlike DELETE)
1054		set=set_columns
1055		(WHERE where_condition)?
1056		/* these options are only valid if we update one table */
1057		({$table.table_count==1}?=>
1058			order_by?
1059			(LIMIT NUMBER)?
1060		)?
1061		-> ^(UPDATE LOW_PRIORITY? IGNORE? $table $set ^(WHERE<com.mysql.clusterj.jdbc.antlr.node.WhereNode> where_condition)? order_by? ^(LIMIT NUMBER)?)
1062	;
1063
1064
1065// $> Update
1066
1067// $< Delete
1068
1069/* both multi table delete trees are basically identical. The FROM and USING nodes are just in there to differentiate between the syntax used, in order to format it correctly
1070   the AST drops potential .* suffixes for the table names, as they are simply syntactic sugar.
1071*/
1072delete
1073@init {
1074boolean multiTableDelete = false;
1075}
1076	:	DELETE
1077// opts+=QUICK causes parser warnings
1078		(options{k=1;}: opts+=LOW_PRIORITY | opts+=IGNORE)*		// the yacc parser accepts any combination and any number of these modifiers, so we do, too.
1079		(	FROM
1080			t+=simple_table_ref_no_alias (DOT MULT {multiTableDelete = true;} )? (COMMA t+=simple_table_ref_no_alias (DOT MULT)? {multiTableDelete = true;} )*
1081			(USING tr=table_references {multiTableDelete = true;})?
1082			(WHERE where_condition)?
1083			({multiTableDelete == false}?=>
1084				order_by?
1085				(LIMIT NUMBER)?
1086			)?
1087				-> {multiTableDelete}? ^(DELETE<com.mysql.clusterj.jdbc.antlr.node.DeleteNode> ^(OPTIONS $opts+)? ^(TABLE $t)+ ^(USING $tr) ^(WHERE<com.mysql.clusterj.jdbc.antlr.node.WhereNode> where_condition)?)
1088				-> ^(DELETE<com.mysql.clusterj.jdbc.antlr.node.DeleteNode> ^(OPTIONS $opts+)? ^(TABLE $t) ^(WHERE<com.mysql.clusterj.jdbc.antlr.node.WhereNode> where_condition)? order_by? ^(LIMIT NUMBER)?)
1089
1090		|	t+=simple_table_ref_no_alias (DOT MULT)? (COMMA t+=simple_table_ref_no_alias (DOT MULT)?)*
1091			FROM tr=table_references
1092			(WHERE where_condition)?			-> ^(DELETE ^(OPTIONS $opts+)? ^(TABLE $t)+ ^(FROM $tr) ^(WHERE<com.mysql.clusterj.jdbc.antlr.node.WhereNode> where_condition)?)
1093		)
1094	;
1095
1096// $> Delete
1097
1098// $< Lock tables
1099
1100lockTables
1101	:	LOCK TABLES tables+=lock_table_ref (COMMA tables+=lock_table_ref)*	-> ^(LOCK $tables)
1102	|	UNLOCK TABLES														-> ^(UNLOCK TABLES)
1103	;
1104
1105lock_table_ref
1106	:	simple_table_ref_alias
1107		(	READ  (LOCAL )?					-> ^(READ simple_table_ref_alias LOCAL?)
1108		|	(LOW_PRIORITY )? WRITE 			-> ^(WRITE simple_table_ref_alias LOW_PRIORITY?)
1109		)
1110	;
1111
1112// $> Lock tables
1113
1114// $> DML
1115
1116// $< DDL
1117
1118// $< Create Table
1119
1120create_table
1121	:	CREATE (TEMPORARY )? TABLE
1122		(IF NOT EXISTS )?
1123		tableName=simple_table_ref_no_alias
1124		LPAREN create+=create_definition (COMMA create+=create_definition)* RPAREN
1125		-> ^(CREATE_TABLE
1126				TEMPORARY?
1127				EXISTS?
1128				simple_table_ref_no_alias
1129				^(DEFINITIONS $create+)
1130			)
1131	;
1132
1133create_definition
1134	:	colName=ident column_definition	-> ^(DEFINITION $colName column_definition)
1135	;
1136
1137// $> Create Table
1138
1139column_definition
1140
1141	:	data_type
1142		(notSym=NOT NULL | nullSym=NULL)?
1143		(DEFAULT literal)?		// TODO check whether literal covers all the legal values
1144		autoInc=AUTO_INCREMENT?
1145		(UNIQUE uniqueKey=KEY? | PRIMARY? generalKey=KEY)?
1146		(COMMENT STRING)?
1147		(reference_definition )?
1148		// TODO the following two are NDB specific, skipping for now.
1149//		(COLUMN_FORMAT (FIXED|DYNAMIC|DEFAULT))?
1150//		(STORAGE (DISK|MEMORY))?
1151		-> ^(TYPE data_type
1152				$notSym?
1153				($nullSym)?
1154				^(DEFAULT literal)?
1155				($autoInc)?
1156				UNIQUE? PRIMARY? KEY?
1157			)
1158	;
1159
1160data_type
1161	:	BIT
1162		( LPAREN NUMBER  RPAREN )?
1163	|	(	TINYINT
1164		|	SMALLINT
1165		|	MEDIUMINT
1166		|	INT
1167		|	INTEGER
1168		|	BIGINT
1169		)
1170		(LPAREN NUMBER  RPAREN)?
1171		(SIGNED | UNSIGNED )?
1172		(ZEROFILL )?
1173	|	(	REAL
1174		|	DOUBLE
1175		|	FLOAT
1176		|	DECIMAL
1177		|	NUMERIC
1178		)
1179		(LPAREN num1=NUMBER COMMA num2=NUMBER RPAREN )?
1180		(SIGNED | UNSIGNED )?
1181		(ZEROFILL )?
1182	|	DATE
1183	|	TIME
1184	|	TIMESTAMP
1185	|	DATETIME
1186	|	YEAR
1187	|	TINYBLOB
1188	|	BLOB
1189	|	MEDIUMBLOB
1190	|	LONGBLOB
1191	|	(	CHAR
1192		|	VARCHAR
1193		)
1194		LPAREN NUMBER  RPAREN
1195		(charset )?
1196		(collate )?
1197	|	(	BINARY
1198		|	VARBINARY
1199		)
1200		LPAREN NUMBER  RPAREN
1201	|	(	TINYTEXT
1202		|	TEXT
1203		|	MEDIUMTEXT
1204		|	LONGTEXT
1205		)
1206		(BINARY )?
1207		(charset )?
1208		(collate )?
1209	|	(	ENUM
1210		|	SET
1211		)
1212		LPAREN values+=STRING (COMMA values+=STRING)* RPAREN
1213		(charset )?
1214		(collate )?
1215	;
1216
1217charset
1218	:	CHARACTER SET
1219		(	ID
1220		|	STRING
1221		)
1222	;
1223
1224collate
1225	:	COLLATE
1226		(	ID
1227		|	STRING
1228		)
1229	;
1230
1231reference_definition
1232	:	RESTRICT
1233	|	CASCADE
1234	|	SET NULL
1235	|	NO ACTION
1236	;
1237// $> DDL
1238