Annotation of embedaddon/sqlite3/src/parse.y, revision 1.1.1.1
1.1 misho 1: /*
2: ** 2001 September 15
3: **
4: ** The author disclaims copyright to this source code. In place of
5: ** a legal notice, here is a blessing:
6: **
7: ** May you do good and not evil.
8: ** May you find forgiveness for yourself and forgive others.
9: ** May you share freely, never taking more than you give.
10: **
11: *************************************************************************
12: ** This file contains SQLite's grammar for SQL. Process this file
13: ** using the lemon parser generator to generate C code that runs
14: ** the parser. Lemon will also generate a header file containing
15: ** numeric codes for all of the tokens.
16: */
17:
18: // All token codes are small integers with #defines that begin with "TK_"
19: %token_prefix TK_
20:
21: // The type of the data attached to each token is Token. This is also the
22: // default type for non-terminals.
23: //
24: %token_type {Token}
25: %default_type {Token}
26:
27: // The generated parser function takes a 4th argument as follows:
28: %extra_argument {Parse *pParse}
29:
30: // This code runs whenever there is a syntax error
31: //
32: %syntax_error {
33: UNUSED_PARAMETER(yymajor); /* Silence some compiler warnings */
34: assert( TOKEN.z[0] ); /* The tokenizer always gives us a token */
35: sqlite3ErrorMsg(pParse, "near \"%T\": syntax error", &TOKEN);
36: }
37: %stack_overflow {
38: UNUSED_PARAMETER(yypMinor); /* Silence some compiler warnings */
39: sqlite3ErrorMsg(pParse, "parser stack overflow");
40: }
41:
42: // The name of the generated procedure that implements the parser
43: // is as follows:
44: %name sqlite3Parser
45:
46: // The following text is included near the beginning of the C source
47: // code file that implements the parser.
48: //
49: %include {
50: #include "sqliteInt.h"
51:
52: /*
53: ** Disable all error recovery processing in the parser push-down
54: ** automaton.
55: */
56: #define YYNOERRORRECOVERY 1
57:
58: /*
59: ** Make yytestcase() the same as testcase()
60: */
61: #define yytestcase(X) testcase(X)
62:
63: /*
64: ** An instance of this structure holds information about the
65: ** LIMIT clause of a SELECT statement.
66: */
67: struct LimitVal {
68: Expr *pLimit; /* The LIMIT expression. NULL if there is no limit */
69: Expr *pOffset; /* The OFFSET expression. NULL if there is none */
70: };
71:
72: /*
73: ** An instance of this structure is used to store the LIKE,
74: ** GLOB, NOT LIKE, and NOT GLOB operators.
75: */
76: struct LikeOp {
77: Token eOperator; /* "like" or "glob" or "regexp" */
78: int not; /* True if the NOT keyword is present */
79: };
80:
81: /*
82: ** An instance of the following structure describes the event of a
83: ** TRIGGER. "a" is the event type, one of TK_UPDATE, TK_INSERT,
84: ** TK_DELETE, or TK_INSTEAD. If the event is of the form
85: **
86: ** UPDATE ON (a,b,c)
87: **
88: ** Then the "b" IdList records the list "a,b,c".
89: */
90: struct TrigEvent { int a; IdList * b; };
91:
92: /*
93: ** An instance of this structure holds the ATTACH key and the key type.
94: */
95: struct AttachKey { int type; Token key; };
96:
97: } // end %include
98:
99: // Input is a single SQL command
100: input ::= cmdlist.
101: cmdlist ::= cmdlist ecmd.
102: cmdlist ::= ecmd.
103: ecmd ::= SEMI.
104: ecmd ::= explain cmdx SEMI.
105: explain ::= . { sqlite3BeginParse(pParse, 0); }
106: %ifndef SQLITE_OMIT_EXPLAIN
107: explain ::= EXPLAIN. { sqlite3BeginParse(pParse, 1); }
108: explain ::= EXPLAIN QUERY PLAN. { sqlite3BeginParse(pParse, 2); }
109: %endif SQLITE_OMIT_EXPLAIN
110: cmdx ::= cmd. { sqlite3FinishCoding(pParse); }
111:
112: ///////////////////// Begin and end transactions. ////////////////////////////
113: //
114:
115: cmd ::= BEGIN transtype(Y) trans_opt. {sqlite3BeginTransaction(pParse, Y);}
116: trans_opt ::= .
117: trans_opt ::= TRANSACTION.
118: trans_opt ::= TRANSACTION nm.
119: %type transtype {int}
120: transtype(A) ::= . {A = TK_DEFERRED;}
121: transtype(A) ::= DEFERRED(X). {A = @X;}
122: transtype(A) ::= IMMEDIATE(X). {A = @X;}
123: transtype(A) ::= EXCLUSIVE(X). {A = @X;}
124: cmd ::= COMMIT trans_opt. {sqlite3CommitTransaction(pParse);}
125: cmd ::= END trans_opt. {sqlite3CommitTransaction(pParse);}
126: cmd ::= ROLLBACK trans_opt. {sqlite3RollbackTransaction(pParse);}
127:
128: savepoint_opt ::= SAVEPOINT.
129: savepoint_opt ::= .
130: cmd ::= SAVEPOINT nm(X). {
131: sqlite3Savepoint(pParse, SAVEPOINT_BEGIN, &X);
132: }
133: cmd ::= RELEASE savepoint_opt nm(X). {
134: sqlite3Savepoint(pParse, SAVEPOINT_RELEASE, &X);
135: }
136: cmd ::= ROLLBACK trans_opt TO savepoint_opt nm(X). {
137: sqlite3Savepoint(pParse, SAVEPOINT_ROLLBACK, &X);
138: }
139:
140: ///////////////////// The CREATE TABLE statement ////////////////////////////
141: //
142: cmd ::= create_table create_table_args.
143: create_table ::= createkw temp(T) TABLE ifnotexists(E) nm(Y) dbnm(Z). {
144: sqlite3StartTable(pParse,&Y,&Z,T,0,0,E);
145: }
146: createkw(A) ::= CREATE(X). {
147: pParse->db->lookaside.bEnabled = 0;
148: A = X;
149: }
150: %type ifnotexists {int}
151: ifnotexists(A) ::= . {A = 0;}
152: ifnotexists(A) ::= IF NOT EXISTS. {A = 1;}
153: %type temp {int}
154: %ifndef SQLITE_OMIT_TEMPDB
155: temp(A) ::= TEMP. {A = 1;}
156: %endif SQLITE_OMIT_TEMPDB
157: temp(A) ::= . {A = 0;}
158: create_table_args ::= LP columnlist conslist_opt(X) RP(Y). {
159: sqlite3EndTable(pParse,&X,&Y,0);
160: }
161: create_table_args ::= AS select(S). {
162: sqlite3EndTable(pParse,0,0,S);
163: sqlite3SelectDelete(pParse->db, S);
164: }
165: columnlist ::= columnlist COMMA column.
166: columnlist ::= column.
167:
168: // A "column" is a complete description of a single column in a
169: // CREATE TABLE statement. This includes the column name, its
170: // datatype, and other keywords such as PRIMARY KEY, UNIQUE, REFERENCES,
171: // NOT NULL and so forth.
172: //
173: column(A) ::= columnid(X) type carglist. {
174: A.z = X.z;
175: A.n = (int)(pParse->sLastToken.z-X.z) + pParse->sLastToken.n;
176: }
177: columnid(A) ::= nm(X). {
178: sqlite3AddColumn(pParse,&X);
179: A = X;
180: }
181:
182:
183: // An IDENTIFIER can be a generic identifier, or one of several
184: // keywords. Any non-standard keyword can also be an identifier.
185: //
186: %type id {Token}
187: id(A) ::= ID(X). {A = X;}
188: id(A) ::= INDEXED(X). {A = X;}
189:
190: // The following directive causes tokens ABORT, AFTER, ASC, etc. to
191: // fallback to ID if they will not parse as their original value.
192: // This obviates the need for the "id" nonterminal.
193: //
194: %fallback ID
195: ABORT ACTION AFTER ANALYZE ASC ATTACH BEFORE BEGIN BY CASCADE CAST COLUMNKW
196: CONFLICT DATABASE DEFERRED DESC DETACH EACH END EXCLUSIVE EXPLAIN FAIL FOR
197: IGNORE IMMEDIATE INITIALLY INSTEAD LIKE_KW MATCH NO PLAN
198: QUERY KEY OF OFFSET PRAGMA RAISE RELEASE REPLACE RESTRICT ROW ROLLBACK
199: SAVEPOINT TEMP TRIGGER VACUUM VIEW VIRTUAL
200: %ifdef SQLITE_OMIT_COMPOUND_SELECT
201: EXCEPT INTERSECT UNION
202: %endif SQLITE_OMIT_COMPOUND_SELECT
203: REINDEX RENAME CTIME_KW IF
204: .
205: %wildcard ANY.
206:
207: // Define operator precedence early so that this is the first occurance
208: // of the operator tokens in the grammer. Keeping the operators together
209: // causes them to be assigned integer values that are close together,
210: // which keeps parser tables smaller.
211: //
212: // The token values assigned to these symbols is determined by the order
213: // in which lemon first sees them. It must be the case that ISNULL/NOTNULL,
214: // NE/EQ, GT/LE, and GE/LT are separated by only a single value. See
215: // the sqlite3ExprIfFalse() routine for additional information on this
216: // constraint.
217: //
218: %left OR.
219: %left AND.
220: %right NOT.
221: %left IS MATCH LIKE_KW BETWEEN IN ISNULL NOTNULL NE EQ.
222: %left GT LE LT GE.
223: %right ESCAPE.
224: %left BITAND BITOR LSHIFT RSHIFT.
225: %left PLUS MINUS.
226: %left STAR SLASH REM.
227: %left CONCAT.
228: %left COLLATE.
229: %right BITNOT.
230:
231: // And "ids" is an identifer-or-string.
232: //
233: %type ids {Token}
234: ids(A) ::= ID|STRING(X). {A = X;}
235:
236: // The name of a column or table can be any of the following:
237: //
238: %type nm {Token}
239: nm(A) ::= id(X). {A = X;}
240: nm(A) ::= STRING(X). {A = X;}
241: nm(A) ::= JOIN_KW(X). {A = X;}
242:
243: // A typetoken is really one or more tokens that form a type name such
244: // as can be found after the column name in a CREATE TABLE statement.
245: // Multiple tokens are concatenated to form the value of the typetoken.
246: //
247: %type typetoken {Token}
248: type ::= .
249: type ::= typetoken(X). {sqlite3AddColumnType(pParse,&X);}
250: typetoken(A) ::= typename(X). {A = X;}
251: typetoken(A) ::= typename(X) LP signed RP(Y). {
252: A.z = X.z;
253: A.n = (int)(&Y.z[Y.n] - X.z);
254: }
255: typetoken(A) ::= typename(X) LP signed COMMA signed RP(Y). {
256: A.z = X.z;
257: A.n = (int)(&Y.z[Y.n] - X.z);
258: }
259: %type typename {Token}
260: typename(A) ::= ids(X). {A = X;}
261: typename(A) ::= typename(X) ids(Y). {A.z=X.z; A.n=Y.n+(int)(Y.z-X.z);}
262: signed ::= plus_num.
263: signed ::= minus_num.
264:
265: // "carglist" is a list of additional constraints that come after the
266: // column name and column type in a CREATE TABLE statement.
267: //
268: carglist ::= carglist carg.
269: carglist ::= .
270: carg ::= CONSTRAINT nm ccons.
271: carg ::= ccons.
272: ccons ::= DEFAULT term(X). {sqlite3AddDefaultValue(pParse,&X);}
273: ccons ::= DEFAULT LP expr(X) RP. {sqlite3AddDefaultValue(pParse,&X);}
274: ccons ::= DEFAULT PLUS term(X). {sqlite3AddDefaultValue(pParse,&X);}
275: ccons ::= DEFAULT MINUS(A) term(X). {
276: ExprSpan v;
277: v.pExpr = sqlite3PExpr(pParse, TK_UMINUS, X.pExpr, 0, 0);
278: v.zStart = A.z;
279: v.zEnd = X.zEnd;
280: sqlite3AddDefaultValue(pParse,&v);
281: }
282: ccons ::= DEFAULT id(X). {
283: ExprSpan v;
284: spanExpr(&v, pParse, TK_STRING, &X);
285: sqlite3AddDefaultValue(pParse,&v);
286: }
287:
288: // In addition to the type name, we also care about the primary key and
289: // UNIQUE constraints.
290: //
291: ccons ::= NULL onconf.
292: ccons ::= NOT NULL onconf(R). {sqlite3AddNotNull(pParse, R);}
293: ccons ::= PRIMARY KEY sortorder(Z) onconf(R) autoinc(I).
294: {sqlite3AddPrimaryKey(pParse,0,R,I,Z);}
295: ccons ::= UNIQUE onconf(R). {sqlite3CreateIndex(pParse,0,0,0,0,R,0,0,0,0);}
296: ccons ::= CHECK LP expr(X) RP. {sqlite3AddCheckConstraint(pParse,X.pExpr);}
297: ccons ::= REFERENCES nm(T) idxlist_opt(TA) refargs(R).
298: {sqlite3CreateForeignKey(pParse,0,&T,TA,R);}
299: ccons ::= defer_subclause(D). {sqlite3DeferForeignKey(pParse,D);}
300: ccons ::= COLLATE ids(C). {sqlite3AddCollateType(pParse, &C);}
301:
302: // The optional AUTOINCREMENT keyword
303: %type autoinc {int}
304: autoinc(X) ::= . {X = 0;}
305: autoinc(X) ::= AUTOINCR. {X = 1;}
306:
307: // The next group of rules parses the arguments to a REFERENCES clause
308: // that determine if the referential integrity checking is deferred or
309: // or immediate and which determine what action to take if a ref-integ
310: // check fails.
311: //
312: %type refargs {int}
313: refargs(A) ::= . { A = OE_None*0x0101; /* EV: R-19803-45884 */}
314: refargs(A) ::= refargs(X) refarg(Y). { A = (X & ~Y.mask) | Y.value; }
315: %type refarg {struct {int value; int mask;}}
316: refarg(A) ::= MATCH nm. { A.value = 0; A.mask = 0x000000; }
317: refarg(A) ::= ON INSERT refact. { A.value = 0; A.mask = 0x000000; }
318: refarg(A) ::= ON DELETE refact(X). { A.value = X; A.mask = 0x0000ff; }
319: refarg(A) ::= ON UPDATE refact(X). { A.value = X<<8; A.mask = 0x00ff00; }
320: %type refact {int}
321: refact(A) ::= SET NULL. { A = OE_SetNull; /* EV: R-33326-45252 */}
322: refact(A) ::= SET DEFAULT. { A = OE_SetDflt; /* EV: R-33326-45252 */}
323: refact(A) ::= CASCADE. { A = OE_Cascade; /* EV: R-33326-45252 */}
324: refact(A) ::= RESTRICT. { A = OE_Restrict; /* EV: R-33326-45252 */}
325: refact(A) ::= NO ACTION. { A = OE_None; /* EV: R-33326-45252 */}
326: %type defer_subclause {int}
327: defer_subclause(A) ::= NOT DEFERRABLE init_deferred_pred_opt. {A = 0;}
328: defer_subclause(A) ::= DEFERRABLE init_deferred_pred_opt(X). {A = X;}
329: %type init_deferred_pred_opt {int}
330: init_deferred_pred_opt(A) ::= . {A = 0;}
331: init_deferred_pred_opt(A) ::= INITIALLY DEFERRED. {A = 1;}
332: init_deferred_pred_opt(A) ::= INITIALLY IMMEDIATE. {A = 0;}
333:
334: // For the time being, the only constraint we care about is the primary
335: // key and UNIQUE. Both create indices.
336: //
337: conslist_opt(A) ::= . {A.n = 0; A.z = 0;}
338: conslist_opt(A) ::= COMMA(X) conslist. {A = X;}
339: conslist ::= conslist COMMA tcons.
340: conslist ::= conslist tcons.
341: conslist ::= tcons.
342: tcons ::= CONSTRAINT nm.
343: tcons ::= PRIMARY KEY LP idxlist(X) autoinc(I) RP onconf(R).
344: {sqlite3AddPrimaryKey(pParse,X,R,I,0);}
345: tcons ::= UNIQUE LP idxlist(X) RP onconf(R).
346: {sqlite3CreateIndex(pParse,0,0,0,X,R,0,0,0,0);}
347: tcons ::= CHECK LP expr(E) RP onconf.
348: {sqlite3AddCheckConstraint(pParse,E.pExpr);}
349: tcons ::= FOREIGN KEY LP idxlist(FA) RP
350: REFERENCES nm(T) idxlist_opt(TA) refargs(R) defer_subclause_opt(D). {
351: sqlite3CreateForeignKey(pParse, FA, &T, TA, R);
352: sqlite3DeferForeignKey(pParse, D);
353: }
354: %type defer_subclause_opt {int}
355: defer_subclause_opt(A) ::= . {A = 0;}
356: defer_subclause_opt(A) ::= defer_subclause(X). {A = X;}
357:
358: // The following is a non-standard extension that allows us to declare the
359: // default behavior when there is a constraint conflict.
360: //
361: %type onconf {int}
362: %type orconf {u8}
363: %type resolvetype {int}
364: onconf(A) ::= . {A = OE_Default;}
365: onconf(A) ::= ON CONFLICT resolvetype(X). {A = X;}
366: orconf(A) ::= . {A = OE_Default;}
367: orconf(A) ::= OR resolvetype(X). {A = (u8)X;}
368: resolvetype(A) ::= raisetype(X). {A = X;}
369: resolvetype(A) ::= IGNORE. {A = OE_Ignore;}
370: resolvetype(A) ::= REPLACE. {A = OE_Replace;}
371:
372: ////////////////////////// The DROP TABLE /////////////////////////////////////
373: //
374: cmd ::= DROP TABLE ifexists(E) fullname(X). {
375: sqlite3DropTable(pParse, X, 0, E);
376: }
377: %type ifexists {int}
378: ifexists(A) ::= IF EXISTS. {A = 1;}
379: ifexists(A) ::= . {A = 0;}
380:
381: ///////////////////// The CREATE VIEW statement /////////////////////////////
382: //
383: %ifndef SQLITE_OMIT_VIEW
384: cmd ::= createkw(X) temp(T) VIEW ifnotexists(E) nm(Y) dbnm(Z) AS select(S). {
385: sqlite3CreateView(pParse, &X, &Y, &Z, S, T, E);
386: }
387: cmd ::= DROP VIEW ifexists(E) fullname(X). {
388: sqlite3DropTable(pParse, X, 1, E);
389: }
390: %endif SQLITE_OMIT_VIEW
391:
392: //////////////////////// The SELECT statement /////////////////////////////////
393: //
394: cmd ::= select(X). {
395: SelectDest dest = {SRT_Output, 0, 0, 0, 0};
396: sqlite3Select(pParse, X, &dest);
397: sqlite3ExplainBegin(pParse->pVdbe);
398: sqlite3ExplainSelect(pParse->pVdbe, X);
399: sqlite3ExplainFinish(pParse->pVdbe);
400: sqlite3SelectDelete(pParse->db, X);
401: }
402:
403: %type select {Select*}
404: %destructor select {sqlite3SelectDelete(pParse->db, $$);}
405: %type oneselect {Select*}
406: %destructor oneselect {sqlite3SelectDelete(pParse->db, $$);}
407:
408: select(A) ::= oneselect(X). {A = X;}
409: %ifndef SQLITE_OMIT_COMPOUND_SELECT
410: select(A) ::= select(X) multiselect_op(Y) oneselect(Z). {
411: if( Z ){
412: Z->op = (u8)Y;
413: Z->pPrior = X;
414: }else{
415: sqlite3SelectDelete(pParse->db, X);
416: }
417: A = Z;
418: }
419: %type multiselect_op {int}
420: multiselect_op(A) ::= UNION(OP). {A = @OP;}
421: multiselect_op(A) ::= UNION ALL. {A = TK_ALL;}
422: multiselect_op(A) ::= EXCEPT|INTERSECT(OP). {A = @OP;}
423: %endif SQLITE_OMIT_COMPOUND_SELECT
424: oneselect(A) ::= SELECT distinct(D) selcollist(W) from(X) where_opt(Y)
425: groupby_opt(P) having_opt(Q) orderby_opt(Z) limit_opt(L). {
426: A = sqlite3SelectNew(pParse,W,X,Y,P,Q,Z,D,L.pLimit,L.pOffset);
427: }
428:
429: // The "distinct" nonterminal is true (1) if the DISTINCT keyword is
430: // present and false (0) if it is not.
431: //
432: %type distinct {int}
433: distinct(A) ::= DISTINCT. {A = 1;}
434: distinct(A) ::= ALL. {A = 0;}
435: distinct(A) ::= . {A = 0;}
436:
437: // selcollist is a list of expressions that are to become the return
438: // values of the SELECT statement. The "*" in statements like
439: // "SELECT * FROM ..." is encoded as a special expression with an
440: // opcode of TK_ALL.
441: //
442: %type selcollist {ExprList*}
443: %destructor selcollist {sqlite3ExprListDelete(pParse->db, $$);}
444: %type sclp {ExprList*}
445: %destructor sclp {sqlite3ExprListDelete(pParse->db, $$);}
446: sclp(A) ::= selcollist(X) COMMA. {A = X;}
447: sclp(A) ::= . {A = 0;}
448: selcollist(A) ::= sclp(P) expr(X) as(Y). {
449: A = sqlite3ExprListAppend(pParse, P, X.pExpr);
450: if( Y.n>0 ) sqlite3ExprListSetName(pParse, A, &Y, 1);
451: sqlite3ExprListSetSpan(pParse,A,&X);
452: }
453: selcollist(A) ::= sclp(P) STAR. {
454: Expr *p = sqlite3Expr(pParse->db, TK_ALL, 0);
455: A = sqlite3ExprListAppend(pParse, P, p);
456: }
457: selcollist(A) ::= sclp(P) nm(X) DOT STAR(Y). {
458: Expr *pRight = sqlite3PExpr(pParse, TK_ALL, 0, 0, &Y);
459: Expr *pLeft = sqlite3PExpr(pParse, TK_ID, 0, 0, &X);
460: Expr *pDot = sqlite3PExpr(pParse, TK_DOT, pLeft, pRight, 0);
461: A = sqlite3ExprListAppend(pParse,P, pDot);
462: }
463:
464: // An option "AS <id>" phrase that can follow one of the expressions that
465: // define the result set, or one of the tables in the FROM clause.
466: //
467: %type as {Token}
468: as(X) ::= AS nm(Y). {X = Y;}
469: as(X) ::= ids(Y). {X = Y;}
470: as(X) ::= . {X.n = 0;}
471:
472:
473: %type seltablist {SrcList*}
474: %destructor seltablist {sqlite3SrcListDelete(pParse->db, $$);}
475: %type stl_prefix {SrcList*}
476: %destructor stl_prefix {sqlite3SrcListDelete(pParse->db, $$);}
477: %type from {SrcList*}
478: %destructor from {sqlite3SrcListDelete(pParse->db, $$);}
479:
480: // A complete FROM clause.
481: //
482: from(A) ::= . {A = sqlite3DbMallocZero(pParse->db, sizeof(*A));}
483: from(A) ::= FROM seltablist(X). {
484: A = X;
485: sqlite3SrcListShiftJoinType(A);
486: }
487:
488: // "seltablist" is a "Select Table List" - the content of the FROM clause
489: // in a SELECT statement. "stl_prefix" is a prefix of this list.
490: //
491: stl_prefix(A) ::= seltablist(X) joinop(Y). {
492: A = X;
493: if( ALWAYS(A && A->nSrc>0) ) A->a[A->nSrc-1].jointype = (u8)Y;
494: }
495: stl_prefix(A) ::= . {A = 0;}
496: seltablist(A) ::= stl_prefix(X) nm(Y) dbnm(D) as(Z) indexed_opt(I) on_opt(N) using_opt(U). {
497: A = sqlite3SrcListAppendFromTerm(pParse,X,&Y,&D,&Z,0,N,U);
498: sqlite3SrcListIndexedBy(pParse, A, &I);
499: }
500: %ifndef SQLITE_OMIT_SUBQUERY
501: seltablist(A) ::= stl_prefix(X) LP select(S) RP
502: as(Z) on_opt(N) using_opt(U). {
503: A = sqlite3SrcListAppendFromTerm(pParse,X,0,0,&Z,S,N,U);
504: }
505: seltablist(A) ::= stl_prefix(X) LP seltablist(F) RP
506: as(Z) on_opt(N) using_opt(U). {
507: if( X==0 && Z.n==0 && N==0 && U==0 ){
508: A = F;
509: }else{
510: Select *pSubquery;
511: sqlite3SrcListShiftJoinType(F);
512: pSubquery = sqlite3SelectNew(pParse,0,F,0,0,0,0,0,0,0);
513: A = sqlite3SrcListAppendFromTerm(pParse,X,0,0,&Z,pSubquery,N,U);
514: }
515: }
516:
517: // A seltablist_paren nonterminal represents anything in a FROM that
518: // is contained inside parentheses. This can be either a subquery or
519: // a grouping of table and subqueries.
520: //
521: // %type seltablist_paren {Select*}
522: // %destructor seltablist_paren {sqlite3SelectDelete(pParse->db, $$);}
523: // seltablist_paren(A) ::= select(S). {A = S;}
524: // seltablist_paren(A) ::= seltablist(F). {
525: // sqlite3SrcListShiftJoinType(F);
526: // A = sqlite3SelectNew(pParse,0,F,0,0,0,0,0,0,0);
527: // }
528: %endif SQLITE_OMIT_SUBQUERY
529:
530: %type dbnm {Token}
531: dbnm(A) ::= . {A.z=0; A.n=0;}
532: dbnm(A) ::= DOT nm(X). {A = X;}
533:
534: %type fullname {SrcList*}
535: %destructor fullname {sqlite3SrcListDelete(pParse->db, $$);}
536: fullname(A) ::= nm(X) dbnm(Y). {A = sqlite3SrcListAppend(pParse->db,0,&X,&Y);}
537:
538: %type joinop {int}
539: %type joinop2 {int}
540: joinop(X) ::= COMMA|JOIN. { X = JT_INNER; }
541: joinop(X) ::= JOIN_KW(A) JOIN. { X = sqlite3JoinType(pParse,&A,0,0); }
542: joinop(X) ::= JOIN_KW(A) nm(B) JOIN. { X = sqlite3JoinType(pParse,&A,&B,0); }
543: joinop(X) ::= JOIN_KW(A) nm(B) nm(C) JOIN.
544: { X = sqlite3JoinType(pParse,&A,&B,&C); }
545:
546: %type on_opt {Expr*}
547: %destructor on_opt {sqlite3ExprDelete(pParse->db, $$);}
548: on_opt(N) ::= ON expr(E). {N = E.pExpr;}
549: on_opt(N) ::= . {N = 0;}
550:
551: // Note that this block abuses the Token type just a little. If there is
552: // no "INDEXED BY" clause, the returned token is empty (z==0 && n==0). If
553: // there is an INDEXED BY clause, then the token is populated as per normal,
554: // with z pointing to the token data and n containing the number of bytes
555: // in the token.
556: //
557: // If there is a "NOT INDEXED" clause, then (z==0 && n==1), which is
558: // normally illegal. The sqlite3SrcListIndexedBy() function
559: // recognizes and interprets this as a special case.
560: //
561: %type indexed_opt {Token}
562: indexed_opt(A) ::= . {A.z=0; A.n=0;}
563: indexed_opt(A) ::= INDEXED BY nm(X). {A = X;}
564: indexed_opt(A) ::= NOT INDEXED. {A.z=0; A.n=1;}
565:
566: %type using_opt {IdList*}
567: %destructor using_opt {sqlite3IdListDelete(pParse->db, $$);}
568: using_opt(U) ::= USING LP inscollist(L) RP. {U = L;}
569: using_opt(U) ::= . {U = 0;}
570:
571:
572: %type orderby_opt {ExprList*}
573: %destructor orderby_opt {sqlite3ExprListDelete(pParse->db, $$);}
574: %type sortlist {ExprList*}
575: %destructor sortlist {sqlite3ExprListDelete(pParse->db, $$);}
576: %type sortitem {Expr*}
577: %destructor sortitem {sqlite3ExprDelete(pParse->db, $$);}
578:
579: orderby_opt(A) ::= . {A = 0;}
580: orderby_opt(A) ::= ORDER BY sortlist(X). {A = X;}
581: sortlist(A) ::= sortlist(X) COMMA sortitem(Y) sortorder(Z). {
582: A = sqlite3ExprListAppend(pParse,X,Y);
583: if( A ) A->a[A->nExpr-1].sortOrder = (u8)Z;
584: }
585: sortlist(A) ::= sortitem(Y) sortorder(Z). {
586: A = sqlite3ExprListAppend(pParse,0,Y);
587: if( A && ALWAYS(A->a) ) A->a[0].sortOrder = (u8)Z;
588: }
589: sortitem(A) ::= expr(X). {A = X.pExpr;}
590:
591: %type sortorder {int}
592:
593: sortorder(A) ::= ASC. {A = SQLITE_SO_ASC;}
594: sortorder(A) ::= DESC. {A = SQLITE_SO_DESC;}
595: sortorder(A) ::= . {A = SQLITE_SO_ASC;}
596:
597: %type groupby_opt {ExprList*}
598: %destructor groupby_opt {sqlite3ExprListDelete(pParse->db, $$);}
599: groupby_opt(A) ::= . {A = 0;}
600: groupby_opt(A) ::= GROUP BY nexprlist(X). {A = X;}
601:
602: %type having_opt {Expr*}
603: %destructor having_opt {sqlite3ExprDelete(pParse->db, $$);}
604: having_opt(A) ::= . {A = 0;}
605: having_opt(A) ::= HAVING expr(X). {A = X.pExpr;}
606:
607: %type limit_opt {struct LimitVal}
608:
609: // The destructor for limit_opt will never fire in the current grammar.
610: // The limit_opt non-terminal only occurs at the end of a single production
611: // rule for SELECT statements. As soon as the rule that create the
612: // limit_opt non-terminal reduces, the SELECT statement rule will also
613: // reduce. So there is never a limit_opt non-terminal on the stack
614: // except as a transient. So there is never anything to destroy.
615: //
616: //%destructor limit_opt {
617: // sqlite3ExprDelete(pParse->db, $$.pLimit);
618: // sqlite3ExprDelete(pParse->db, $$.pOffset);
619: //}
620: limit_opt(A) ::= . {A.pLimit = 0; A.pOffset = 0;}
621: limit_opt(A) ::= LIMIT expr(X). {A.pLimit = X.pExpr; A.pOffset = 0;}
622: limit_opt(A) ::= LIMIT expr(X) OFFSET expr(Y).
623: {A.pLimit = X.pExpr; A.pOffset = Y.pExpr;}
624: limit_opt(A) ::= LIMIT expr(X) COMMA expr(Y).
625: {A.pOffset = X.pExpr; A.pLimit = Y.pExpr;}
626:
627: /////////////////////////// The DELETE statement /////////////////////////////
628: //
629: %ifdef SQLITE_ENABLE_UPDATE_DELETE_LIMIT
630: cmd ::= DELETE FROM fullname(X) indexed_opt(I) where_opt(W)
631: orderby_opt(O) limit_opt(L). {
632: sqlite3SrcListIndexedBy(pParse, X, &I);
633: W = sqlite3LimitWhere(pParse, X, W, O, L.pLimit, L.pOffset, "DELETE");
634: sqlite3DeleteFrom(pParse,X,W);
635: }
636: %endif
637: %ifndef SQLITE_ENABLE_UPDATE_DELETE_LIMIT
638: cmd ::= DELETE FROM fullname(X) indexed_opt(I) where_opt(W). {
639: sqlite3SrcListIndexedBy(pParse, X, &I);
640: sqlite3DeleteFrom(pParse,X,W);
641: }
642: %endif
643:
644: %type where_opt {Expr*}
645: %destructor where_opt {sqlite3ExprDelete(pParse->db, $$);}
646:
647: where_opt(A) ::= . {A = 0;}
648: where_opt(A) ::= WHERE expr(X). {A = X.pExpr;}
649:
650: ////////////////////////// The UPDATE command ////////////////////////////////
651: //
652: %ifdef SQLITE_ENABLE_UPDATE_DELETE_LIMIT
653: cmd ::= UPDATE orconf(R) fullname(X) indexed_opt(I) SET setlist(Y) where_opt(W) orderby_opt(O) limit_opt(L). {
654: sqlite3SrcListIndexedBy(pParse, X, &I);
655: sqlite3ExprListCheckLength(pParse,Y,"set list");
656: W = sqlite3LimitWhere(pParse, X, W, O, L.pLimit, L.pOffset, "UPDATE");
657: sqlite3Update(pParse,X,Y,W,R);
658: }
659: %endif
660: %ifndef SQLITE_ENABLE_UPDATE_DELETE_LIMIT
661: cmd ::= UPDATE orconf(R) fullname(X) indexed_opt(I) SET setlist(Y) where_opt(W). {
662: sqlite3SrcListIndexedBy(pParse, X, &I);
663: sqlite3ExprListCheckLength(pParse,Y,"set list");
664: sqlite3Update(pParse,X,Y,W,R);
665: }
666: %endif
667:
668: %type setlist {ExprList*}
669: %destructor setlist {sqlite3ExprListDelete(pParse->db, $$);}
670:
671: setlist(A) ::= setlist(Z) COMMA nm(X) EQ expr(Y). {
672: A = sqlite3ExprListAppend(pParse, Z, Y.pExpr);
673: sqlite3ExprListSetName(pParse, A, &X, 1);
674: }
675: setlist(A) ::= nm(X) EQ expr(Y). {
676: A = sqlite3ExprListAppend(pParse, 0, Y.pExpr);
677: sqlite3ExprListSetName(pParse, A, &X, 1);
678: }
679:
680: ////////////////////////// The INSERT command /////////////////////////////////
681: //
682: cmd ::= insert_cmd(R) INTO fullname(X) inscollist_opt(F)
683: VALUES LP itemlist(Y) RP.
684: {sqlite3Insert(pParse, X, Y, 0, F, R);}
685: cmd ::= insert_cmd(R) INTO fullname(X) inscollist_opt(F) select(S).
686: {sqlite3Insert(pParse, X, 0, S, F, R);}
687: cmd ::= insert_cmd(R) INTO fullname(X) inscollist_opt(F) DEFAULT VALUES.
688: {sqlite3Insert(pParse, X, 0, 0, F, R);}
689:
690: %type insert_cmd {u8}
691: insert_cmd(A) ::= INSERT orconf(R). {A = R;}
692: insert_cmd(A) ::= REPLACE. {A = OE_Replace;}
693:
694:
695: %type itemlist {ExprList*}
696: %destructor itemlist {sqlite3ExprListDelete(pParse->db, $$);}
697:
698: itemlist(A) ::= itemlist(X) COMMA expr(Y).
699: {A = sqlite3ExprListAppend(pParse,X,Y.pExpr);}
700: itemlist(A) ::= expr(X).
701: {A = sqlite3ExprListAppend(pParse,0,X.pExpr);}
702:
703: %type inscollist_opt {IdList*}
704: %destructor inscollist_opt {sqlite3IdListDelete(pParse->db, $$);}
705: %type inscollist {IdList*}
706: %destructor inscollist {sqlite3IdListDelete(pParse->db, $$);}
707:
708: inscollist_opt(A) ::= . {A = 0;}
709: inscollist_opt(A) ::= LP inscollist(X) RP. {A = X;}
710: inscollist(A) ::= inscollist(X) COMMA nm(Y).
711: {A = sqlite3IdListAppend(pParse->db,X,&Y);}
712: inscollist(A) ::= nm(Y).
713: {A = sqlite3IdListAppend(pParse->db,0,&Y);}
714:
715: /////////////////////////// Expression Processing /////////////////////////////
716: //
717:
718: %type expr {ExprSpan}
719: %destructor expr {sqlite3ExprDelete(pParse->db, $$.pExpr);}
720: %type term {ExprSpan}
721: %destructor term {sqlite3ExprDelete(pParse->db, $$.pExpr);}
722:
723: %include {
724: /* This is a utility routine used to set the ExprSpan.zStart and
725: ** ExprSpan.zEnd values of pOut so that the span covers the complete
726: ** range of text beginning with pStart and going to the end of pEnd.
727: */
728: static void spanSet(ExprSpan *pOut, Token *pStart, Token *pEnd){
729: pOut->zStart = pStart->z;
730: pOut->zEnd = &pEnd->z[pEnd->n];
731: }
732:
733: /* Construct a new Expr object from a single identifier. Use the
734: ** new Expr to populate pOut. Set the span of pOut to be the identifier
735: ** that created the expression.
736: */
737: static void spanExpr(ExprSpan *pOut, Parse *pParse, int op, Token *pValue){
738: pOut->pExpr = sqlite3PExpr(pParse, op, 0, 0, pValue);
739: pOut->zStart = pValue->z;
740: pOut->zEnd = &pValue->z[pValue->n];
741: }
742: }
743:
744: expr(A) ::= term(X). {A = X;}
745: expr(A) ::= LP(B) expr(X) RP(E). {A.pExpr = X.pExpr; spanSet(&A,&B,&E);}
746: term(A) ::= NULL(X). {spanExpr(&A, pParse, @X, &X);}
747: expr(A) ::= id(X). {spanExpr(&A, pParse, TK_ID, &X);}
748: expr(A) ::= JOIN_KW(X). {spanExpr(&A, pParse, TK_ID, &X);}
749: expr(A) ::= nm(X) DOT nm(Y). {
750: Expr *temp1 = sqlite3PExpr(pParse, TK_ID, 0, 0, &X);
751: Expr *temp2 = sqlite3PExpr(pParse, TK_ID, 0, 0, &Y);
752: A.pExpr = sqlite3PExpr(pParse, TK_DOT, temp1, temp2, 0);
753: spanSet(&A,&X,&Y);
754: }
755: expr(A) ::= nm(X) DOT nm(Y) DOT nm(Z). {
756: Expr *temp1 = sqlite3PExpr(pParse, TK_ID, 0, 0, &X);
757: Expr *temp2 = sqlite3PExpr(pParse, TK_ID, 0, 0, &Y);
758: Expr *temp3 = sqlite3PExpr(pParse, TK_ID, 0, 0, &Z);
759: Expr *temp4 = sqlite3PExpr(pParse, TK_DOT, temp2, temp3, 0);
760: A.pExpr = sqlite3PExpr(pParse, TK_DOT, temp1, temp4, 0);
761: spanSet(&A,&X,&Z);
762: }
763: term(A) ::= INTEGER|FLOAT|BLOB(X). {spanExpr(&A, pParse, @X, &X);}
764: term(A) ::= STRING(X). {spanExpr(&A, pParse, @X, &X);}
765: expr(A) ::= REGISTER(X). {
766: /* When doing a nested parse, one can include terms in an expression
767: ** that look like this: #1 #2 ... These terms refer to registers
768: ** in the virtual machine. #N is the N-th register. */
769: if( pParse->nested==0 ){
770: sqlite3ErrorMsg(pParse, "near \"%T\": syntax error", &X);
771: A.pExpr = 0;
772: }else{
773: A.pExpr = sqlite3PExpr(pParse, TK_REGISTER, 0, 0, &X);
774: if( A.pExpr ) sqlite3GetInt32(&X.z[1], &A.pExpr->iTable);
775: }
776: spanSet(&A, &X, &X);
777: }
778: expr(A) ::= VARIABLE(X). {
779: spanExpr(&A, pParse, TK_VARIABLE, &X);
780: sqlite3ExprAssignVarNumber(pParse, A.pExpr);
781: spanSet(&A, &X, &X);
782: }
783: expr(A) ::= expr(E) COLLATE ids(C). {
784: A.pExpr = sqlite3ExprSetCollByToken(pParse, E.pExpr, &C);
785: A.zStart = E.zStart;
786: A.zEnd = &C.z[C.n];
787: }
788: %ifndef SQLITE_OMIT_CAST
789: expr(A) ::= CAST(X) LP expr(E) AS typetoken(T) RP(Y). {
790: A.pExpr = sqlite3PExpr(pParse, TK_CAST, E.pExpr, 0, &T);
791: spanSet(&A,&X,&Y);
792: }
793: %endif SQLITE_OMIT_CAST
794: expr(A) ::= ID(X) LP distinct(D) exprlist(Y) RP(E). {
795: if( Y && Y->nExpr>pParse->db->aLimit[SQLITE_LIMIT_FUNCTION_ARG] ){
796: sqlite3ErrorMsg(pParse, "too many arguments on function %T", &X);
797: }
798: A.pExpr = sqlite3ExprFunction(pParse, Y, &X);
799: spanSet(&A,&X,&E);
800: if( D && A.pExpr ){
801: A.pExpr->flags |= EP_Distinct;
802: }
803: }
804: expr(A) ::= ID(X) LP STAR RP(E). {
805: A.pExpr = sqlite3ExprFunction(pParse, 0, &X);
806: spanSet(&A,&X,&E);
807: }
808: term(A) ::= CTIME_KW(OP). {
809: /* The CURRENT_TIME, CURRENT_DATE, and CURRENT_TIMESTAMP values are
810: ** treated as functions that return constants */
811: A.pExpr = sqlite3ExprFunction(pParse, 0,&OP);
812: if( A.pExpr ){
813: A.pExpr->op = TK_CONST_FUNC;
814: }
815: spanSet(&A, &OP, &OP);
816: }
817:
818: %include {
819: /* This routine constructs a binary expression node out of two ExprSpan
820: ** objects and uses the result to populate a new ExprSpan object.
821: */
822: static void spanBinaryExpr(
823: ExprSpan *pOut, /* Write the result here */
824: Parse *pParse, /* The parsing context. Errors accumulate here */
825: int op, /* The binary operation */
826: ExprSpan *pLeft, /* The left operand */
827: ExprSpan *pRight /* The right operand */
828: ){
829: pOut->pExpr = sqlite3PExpr(pParse, op, pLeft->pExpr, pRight->pExpr, 0);
830: pOut->zStart = pLeft->zStart;
831: pOut->zEnd = pRight->zEnd;
832: }
833: }
834:
835: expr(A) ::= expr(X) AND(OP) expr(Y). {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
836: expr(A) ::= expr(X) OR(OP) expr(Y). {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
837: expr(A) ::= expr(X) LT|GT|GE|LE(OP) expr(Y).
838: {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
839: expr(A) ::= expr(X) EQ|NE(OP) expr(Y). {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
840: expr(A) ::= expr(X) BITAND|BITOR|LSHIFT|RSHIFT(OP) expr(Y).
841: {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
842: expr(A) ::= expr(X) PLUS|MINUS(OP) expr(Y).
843: {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
844: expr(A) ::= expr(X) STAR|SLASH|REM(OP) expr(Y).
845: {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
846: expr(A) ::= expr(X) CONCAT(OP) expr(Y). {spanBinaryExpr(&A,pParse,@OP,&X,&Y);}
847: %type likeop {struct LikeOp}
848: likeop(A) ::= LIKE_KW(X). {A.eOperator = X; A.not = 0;}
849: likeop(A) ::= NOT LIKE_KW(X). {A.eOperator = X; A.not = 1;}
850: likeop(A) ::= MATCH(X). {A.eOperator = X; A.not = 0;}
851: likeop(A) ::= NOT MATCH(X). {A.eOperator = X; A.not = 1;}
852: expr(A) ::= expr(X) likeop(OP) expr(Y). [LIKE_KW] {
853: ExprList *pList;
854: pList = sqlite3ExprListAppend(pParse,0, Y.pExpr);
855: pList = sqlite3ExprListAppend(pParse,pList, X.pExpr);
856: A.pExpr = sqlite3ExprFunction(pParse, pList, &OP.eOperator);
857: if( OP.not ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
858: A.zStart = X.zStart;
859: A.zEnd = Y.zEnd;
860: if( A.pExpr ) A.pExpr->flags |= EP_InfixFunc;
861: }
862: expr(A) ::= expr(X) likeop(OP) expr(Y) ESCAPE expr(E). [LIKE_KW] {
863: ExprList *pList;
864: pList = sqlite3ExprListAppend(pParse,0, Y.pExpr);
865: pList = sqlite3ExprListAppend(pParse,pList, X.pExpr);
866: pList = sqlite3ExprListAppend(pParse,pList, E.pExpr);
867: A.pExpr = sqlite3ExprFunction(pParse, pList, &OP.eOperator);
868: if( OP.not ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
869: A.zStart = X.zStart;
870: A.zEnd = E.zEnd;
871: if( A.pExpr ) A.pExpr->flags |= EP_InfixFunc;
872: }
873:
874: %include {
875: /* Construct an expression node for a unary postfix operator
876: */
877: static void spanUnaryPostfix(
878: ExprSpan *pOut, /* Write the new expression node here */
879: Parse *pParse, /* Parsing context to record errors */
880: int op, /* The operator */
881: ExprSpan *pOperand, /* The operand */
882: Token *pPostOp /* The operand token for setting the span */
883: ){
884: pOut->pExpr = sqlite3PExpr(pParse, op, pOperand->pExpr, 0, 0);
885: pOut->zStart = pOperand->zStart;
886: pOut->zEnd = &pPostOp->z[pPostOp->n];
887: }
888: }
889:
890: expr(A) ::= expr(X) ISNULL|NOTNULL(E). {spanUnaryPostfix(&A,pParse,@E,&X,&E);}
891: expr(A) ::= expr(X) NOT NULL(E). {spanUnaryPostfix(&A,pParse,TK_NOTNULL,&X,&E);}
892:
893: %include {
894: /* A routine to convert a binary TK_IS or TK_ISNOT expression into a
895: ** unary TK_ISNULL or TK_NOTNULL expression. */
896: static void binaryToUnaryIfNull(Parse *pParse, Expr *pY, Expr *pA, int op){
897: sqlite3 *db = pParse->db;
898: if( db->mallocFailed==0 && pY->op==TK_NULL ){
899: pA->op = (u8)op;
900: sqlite3ExprDelete(db, pA->pRight);
901: pA->pRight = 0;
902: }
903: }
904: }
905:
906: // expr1 IS expr2
907: // expr1 IS NOT expr2
908: //
909: // If expr2 is NULL then code as TK_ISNULL or TK_NOTNULL. If expr2
910: // is any other expression, code as TK_IS or TK_ISNOT.
911: //
912: expr(A) ::= expr(X) IS expr(Y). {
913: spanBinaryExpr(&A,pParse,TK_IS,&X,&Y);
914: binaryToUnaryIfNull(pParse, Y.pExpr, A.pExpr, TK_ISNULL);
915: }
916: expr(A) ::= expr(X) IS NOT expr(Y). {
917: spanBinaryExpr(&A,pParse,TK_ISNOT,&X,&Y);
918: binaryToUnaryIfNull(pParse, Y.pExpr, A.pExpr, TK_NOTNULL);
919: }
920:
921: %include {
922: /* Construct an expression node for a unary prefix operator
923: */
924: static void spanUnaryPrefix(
925: ExprSpan *pOut, /* Write the new expression node here */
926: Parse *pParse, /* Parsing context to record errors */
927: int op, /* The operator */
928: ExprSpan *pOperand, /* The operand */
929: Token *pPreOp /* The operand token for setting the span */
930: ){
931: pOut->pExpr = sqlite3PExpr(pParse, op, pOperand->pExpr, 0, 0);
932: pOut->zStart = pPreOp->z;
933: pOut->zEnd = pOperand->zEnd;
934: }
935: }
936:
937:
938:
939: expr(A) ::= NOT(B) expr(X). {spanUnaryPrefix(&A,pParse,@B,&X,&B);}
940: expr(A) ::= BITNOT(B) expr(X). {spanUnaryPrefix(&A,pParse,@B,&X,&B);}
941: expr(A) ::= MINUS(B) expr(X). [BITNOT]
942: {spanUnaryPrefix(&A,pParse,TK_UMINUS,&X,&B);}
943: expr(A) ::= PLUS(B) expr(X). [BITNOT]
944: {spanUnaryPrefix(&A,pParse,TK_UPLUS,&X,&B);}
945:
946: %type between_op {int}
947: between_op(A) ::= BETWEEN. {A = 0;}
948: between_op(A) ::= NOT BETWEEN. {A = 1;}
949: expr(A) ::= expr(W) between_op(N) expr(X) AND expr(Y). [BETWEEN] {
950: ExprList *pList = sqlite3ExprListAppend(pParse,0, X.pExpr);
951: pList = sqlite3ExprListAppend(pParse,pList, Y.pExpr);
952: A.pExpr = sqlite3PExpr(pParse, TK_BETWEEN, W.pExpr, 0, 0);
953: if( A.pExpr ){
954: A.pExpr->x.pList = pList;
955: }else{
956: sqlite3ExprListDelete(pParse->db, pList);
957: }
958: if( N ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
959: A.zStart = W.zStart;
960: A.zEnd = Y.zEnd;
961: }
962: %ifndef SQLITE_OMIT_SUBQUERY
963: %type in_op {int}
964: in_op(A) ::= IN. {A = 0;}
965: in_op(A) ::= NOT IN. {A = 1;}
966: expr(A) ::= expr(X) in_op(N) LP exprlist(Y) RP(E). [IN] {
967: if( Y==0 ){
968: /* Expressions of the form
969: **
970: ** expr1 IN ()
971: ** expr1 NOT IN ()
972: **
973: ** simplify to constants 0 (false) and 1 (true), respectively,
974: ** regardless of the value of expr1.
975: */
976: A.pExpr = sqlite3PExpr(pParse, TK_INTEGER, 0, 0, &sqlite3IntTokens[N]);
977: sqlite3ExprDelete(pParse->db, X.pExpr);
978: }else{
979: A.pExpr = sqlite3PExpr(pParse, TK_IN, X.pExpr, 0, 0);
980: if( A.pExpr ){
981: A.pExpr->x.pList = Y;
982: sqlite3ExprSetHeight(pParse, A.pExpr);
983: }else{
984: sqlite3ExprListDelete(pParse->db, Y);
985: }
986: if( N ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
987: }
988: A.zStart = X.zStart;
989: A.zEnd = &E.z[E.n];
990: }
991: expr(A) ::= LP(B) select(X) RP(E). {
992: A.pExpr = sqlite3PExpr(pParse, TK_SELECT, 0, 0, 0);
993: if( A.pExpr ){
994: A.pExpr->x.pSelect = X;
995: ExprSetProperty(A.pExpr, EP_xIsSelect);
996: sqlite3ExprSetHeight(pParse, A.pExpr);
997: }else{
998: sqlite3SelectDelete(pParse->db, X);
999: }
1000: A.zStart = B.z;
1001: A.zEnd = &E.z[E.n];
1002: }
1003: expr(A) ::= expr(X) in_op(N) LP select(Y) RP(E). [IN] {
1004: A.pExpr = sqlite3PExpr(pParse, TK_IN, X.pExpr, 0, 0);
1005: if( A.pExpr ){
1006: A.pExpr->x.pSelect = Y;
1007: ExprSetProperty(A.pExpr, EP_xIsSelect);
1008: sqlite3ExprSetHeight(pParse, A.pExpr);
1009: }else{
1010: sqlite3SelectDelete(pParse->db, Y);
1011: }
1012: if( N ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
1013: A.zStart = X.zStart;
1014: A.zEnd = &E.z[E.n];
1015: }
1016: expr(A) ::= expr(X) in_op(N) nm(Y) dbnm(Z). [IN] {
1017: SrcList *pSrc = sqlite3SrcListAppend(pParse->db, 0,&Y,&Z);
1018: A.pExpr = sqlite3PExpr(pParse, TK_IN, X.pExpr, 0, 0);
1019: if( A.pExpr ){
1020: A.pExpr->x.pSelect = sqlite3SelectNew(pParse, 0,pSrc,0,0,0,0,0,0,0);
1021: ExprSetProperty(A.pExpr, EP_xIsSelect);
1022: sqlite3ExprSetHeight(pParse, A.pExpr);
1023: }else{
1024: sqlite3SrcListDelete(pParse->db, pSrc);
1025: }
1026: if( N ) A.pExpr = sqlite3PExpr(pParse, TK_NOT, A.pExpr, 0, 0);
1027: A.zStart = X.zStart;
1028: A.zEnd = Z.z ? &Z.z[Z.n] : &Y.z[Y.n];
1029: }
1030: expr(A) ::= EXISTS(B) LP select(Y) RP(E). {
1031: Expr *p = A.pExpr = sqlite3PExpr(pParse, TK_EXISTS, 0, 0, 0);
1032: if( p ){
1033: p->x.pSelect = Y;
1034: ExprSetProperty(p, EP_xIsSelect);
1035: sqlite3ExprSetHeight(pParse, p);
1036: }else{
1037: sqlite3SelectDelete(pParse->db, Y);
1038: }
1039: A.zStart = B.z;
1040: A.zEnd = &E.z[E.n];
1041: }
1042: %endif SQLITE_OMIT_SUBQUERY
1043:
1044: /* CASE expressions */
1045: expr(A) ::= CASE(C) case_operand(X) case_exprlist(Y) case_else(Z) END(E). {
1046: A.pExpr = sqlite3PExpr(pParse, TK_CASE, X, Z, 0);
1047: if( A.pExpr ){
1048: A.pExpr->x.pList = Y;
1049: sqlite3ExprSetHeight(pParse, A.pExpr);
1050: }else{
1051: sqlite3ExprListDelete(pParse->db, Y);
1052: }
1053: A.zStart = C.z;
1054: A.zEnd = &E.z[E.n];
1055: }
1056: %type case_exprlist {ExprList*}
1057: %destructor case_exprlist {sqlite3ExprListDelete(pParse->db, $$);}
1058: case_exprlist(A) ::= case_exprlist(X) WHEN expr(Y) THEN expr(Z). {
1059: A = sqlite3ExprListAppend(pParse,X, Y.pExpr);
1060: A = sqlite3ExprListAppend(pParse,A, Z.pExpr);
1061: }
1062: case_exprlist(A) ::= WHEN expr(Y) THEN expr(Z). {
1063: A = sqlite3ExprListAppend(pParse,0, Y.pExpr);
1064: A = sqlite3ExprListAppend(pParse,A, Z.pExpr);
1065: }
1066: %type case_else {Expr*}
1067: %destructor case_else {sqlite3ExprDelete(pParse->db, $$);}
1068: case_else(A) ::= ELSE expr(X). {A = X.pExpr;}
1069: case_else(A) ::= . {A = 0;}
1070: %type case_operand {Expr*}
1071: %destructor case_operand {sqlite3ExprDelete(pParse->db, $$);}
1072: case_operand(A) ::= expr(X). {A = X.pExpr;}
1073: case_operand(A) ::= . {A = 0;}
1074:
1075: %type exprlist {ExprList*}
1076: %destructor exprlist {sqlite3ExprListDelete(pParse->db, $$);}
1077: %type nexprlist {ExprList*}
1078: %destructor nexprlist {sqlite3ExprListDelete(pParse->db, $$);}
1079:
1080: exprlist(A) ::= nexprlist(X). {A = X;}
1081: exprlist(A) ::= . {A = 0;}
1082: nexprlist(A) ::= nexprlist(X) COMMA expr(Y).
1083: {A = sqlite3ExprListAppend(pParse,X,Y.pExpr);}
1084: nexprlist(A) ::= expr(Y).
1085: {A = sqlite3ExprListAppend(pParse,0,Y.pExpr);}
1086:
1087:
1088: ///////////////////////////// The CREATE INDEX command ///////////////////////
1089: //
1090: cmd ::= createkw(S) uniqueflag(U) INDEX ifnotexists(NE) nm(X) dbnm(D)
1091: ON nm(Y) LP idxlist(Z) RP(E). {
1092: sqlite3CreateIndex(pParse, &X, &D,
1093: sqlite3SrcListAppend(pParse->db,0,&Y,0), Z, U,
1094: &S, &E, SQLITE_SO_ASC, NE);
1095: }
1096:
1097: %type uniqueflag {int}
1098: uniqueflag(A) ::= UNIQUE. {A = OE_Abort;}
1099: uniqueflag(A) ::= . {A = OE_None;}
1100:
1101: %type idxlist {ExprList*}
1102: %destructor idxlist {sqlite3ExprListDelete(pParse->db, $$);}
1103: %type idxlist_opt {ExprList*}
1104: %destructor idxlist_opt {sqlite3ExprListDelete(pParse->db, $$);}
1105:
1106: idxlist_opt(A) ::= . {A = 0;}
1107: idxlist_opt(A) ::= LP idxlist(X) RP. {A = X;}
1108: idxlist(A) ::= idxlist(X) COMMA nm(Y) collate(C) sortorder(Z). {
1109: Expr *p = 0;
1110: if( C.n>0 ){
1111: p = sqlite3Expr(pParse->db, TK_COLUMN, 0);
1112: sqlite3ExprSetCollByToken(pParse, p, &C);
1113: }
1114: A = sqlite3ExprListAppend(pParse,X, p);
1115: sqlite3ExprListSetName(pParse,A,&Y,1);
1116: sqlite3ExprListCheckLength(pParse, A, "index");
1117: if( A ) A->a[A->nExpr-1].sortOrder = (u8)Z;
1118: }
1119: idxlist(A) ::= nm(Y) collate(C) sortorder(Z). {
1120: Expr *p = 0;
1121: if( C.n>0 ){
1122: p = sqlite3PExpr(pParse, TK_COLUMN, 0, 0, 0);
1123: sqlite3ExprSetCollByToken(pParse, p, &C);
1124: }
1125: A = sqlite3ExprListAppend(pParse,0, p);
1126: sqlite3ExprListSetName(pParse, A, &Y, 1);
1127: sqlite3ExprListCheckLength(pParse, A, "index");
1128: if( A ) A->a[A->nExpr-1].sortOrder = (u8)Z;
1129: }
1130:
1131: %type collate {Token}
1132: collate(C) ::= . {C.z = 0; C.n = 0;}
1133: collate(C) ::= COLLATE ids(X). {C = X;}
1134:
1135:
1136: ///////////////////////////// The DROP INDEX command /////////////////////////
1137: //
1138: cmd ::= DROP INDEX ifexists(E) fullname(X). {sqlite3DropIndex(pParse, X, E);}
1139:
1140: ///////////////////////////// The VACUUM command /////////////////////////////
1141: //
1142: %ifndef SQLITE_OMIT_VACUUM
1143: %ifndef SQLITE_OMIT_ATTACH
1144: cmd ::= VACUUM. {sqlite3Vacuum(pParse);}
1145: cmd ::= VACUUM nm. {sqlite3Vacuum(pParse);}
1146: %endif SQLITE_OMIT_ATTACH
1147: %endif SQLITE_OMIT_VACUUM
1148:
1149: ///////////////////////////// The PRAGMA command /////////////////////////////
1150: //
1151: %ifndef SQLITE_OMIT_PRAGMA
1152: cmd ::= PRAGMA nm(X) dbnm(Z). {sqlite3Pragma(pParse,&X,&Z,0,0);}
1153: cmd ::= PRAGMA nm(X) dbnm(Z) EQ nmnum(Y). {sqlite3Pragma(pParse,&X,&Z,&Y,0);}
1154: cmd ::= PRAGMA nm(X) dbnm(Z) LP nmnum(Y) RP. {sqlite3Pragma(pParse,&X,&Z,&Y,0);}
1155: cmd ::= PRAGMA nm(X) dbnm(Z) EQ minus_num(Y).
1156: {sqlite3Pragma(pParse,&X,&Z,&Y,1);}
1157: cmd ::= PRAGMA nm(X) dbnm(Z) LP minus_num(Y) RP.
1158: {sqlite3Pragma(pParse,&X,&Z,&Y,1);}
1159:
1160: nmnum(A) ::= plus_num(X). {A = X;}
1161: nmnum(A) ::= nm(X). {A = X;}
1162: nmnum(A) ::= ON(X). {A = X;}
1163: nmnum(A) ::= DELETE(X). {A = X;}
1164: nmnum(A) ::= DEFAULT(X). {A = X;}
1165: %endif SQLITE_OMIT_PRAGMA
1166: plus_num(A) ::= plus_opt number(X). {A = X;}
1167: minus_num(A) ::= MINUS number(X). {A = X;}
1168: number(A) ::= INTEGER|FLOAT(X). {A = X;}
1169: plus_opt ::= PLUS.
1170: plus_opt ::= .
1171:
1172: //////////////////////////// The CREATE TRIGGER command /////////////////////
1173:
1174: %ifndef SQLITE_OMIT_TRIGGER
1175:
1176: cmd ::= createkw trigger_decl(A) BEGIN trigger_cmd_list(S) END(Z). {
1177: Token all;
1178: all.z = A.z;
1179: all.n = (int)(Z.z - A.z) + Z.n;
1180: sqlite3FinishTrigger(pParse, S, &all);
1181: }
1182:
1183: trigger_decl(A) ::= temp(T) TRIGGER ifnotexists(NOERR) nm(B) dbnm(Z)
1184: trigger_time(C) trigger_event(D)
1185: ON fullname(E) foreach_clause when_clause(G). {
1186: sqlite3BeginTrigger(pParse, &B, &Z, C, D.a, D.b, E, G, T, NOERR);
1187: A = (Z.n==0?B:Z);
1188: }
1189:
1190: %type trigger_time {int}
1191: trigger_time(A) ::= BEFORE. { A = TK_BEFORE; }
1192: trigger_time(A) ::= AFTER. { A = TK_AFTER; }
1193: trigger_time(A) ::= INSTEAD OF. { A = TK_INSTEAD;}
1194: trigger_time(A) ::= . { A = TK_BEFORE; }
1195:
1196: %type trigger_event {struct TrigEvent}
1197: %destructor trigger_event {sqlite3IdListDelete(pParse->db, $$.b);}
1198: trigger_event(A) ::= DELETE|INSERT(OP). {A.a = @OP; A.b = 0;}
1199: trigger_event(A) ::= UPDATE(OP). {A.a = @OP; A.b = 0;}
1200: trigger_event(A) ::= UPDATE OF inscollist(X). {A.a = TK_UPDATE; A.b = X;}
1201:
1202: foreach_clause ::= .
1203: foreach_clause ::= FOR EACH ROW.
1204:
1205: %type when_clause {Expr*}
1206: %destructor when_clause {sqlite3ExprDelete(pParse->db, $$);}
1207: when_clause(A) ::= . { A = 0; }
1208: when_clause(A) ::= WHEN expr(X). { A = X.pExpr; }
1209:
1210: %type trigger_cmd_list {TriggerStep*}
1211: %destructor trigger_cmd_list {sqlite3DeleteTriggerStep(pParse->db, $$);}
1212: trigger_cmd_list(A) ::= trigger_cmd_list(Y) trigger_cmd(X) SEMI. {
1213: assert( Y!=0 );
1214: Y->pLast->pNext = X;
1215: Y->pLast = X;
1216: A = Y;
1217: }
1218: trigger_cmd_list(A) ::= trigger_cmd(X) SEMI. {
1219: assert( X!=0 );
1220: X->pLast = X;
1221: A = X;
1222: }
1223:
1224: // Disallow qualified table names on INSERT, UPDATE, and DELETE statements
1225: // within a trigger. The table to INSERT, UPDATE, or DELETE is always in
1226: // the same database as the table that the trigger fires on.
1227: //
1228: %type trnm {Token}
1229: trnm(A) ::= nm(X). {A = X;}
1230: trnm(A) ::= nm DOT nm(X). {
1231: A = X;
1232: sqlite3ErrorMsg(pParse,
1233: "qualified table names are not allowed on INSERT, UPDATE, and DELETE "
1234: "statements within triggers");
1235: }
1236:
1237: // Disallow the INDEX BY and NOT INDEXED clauses on UPDATE and DELETE
1238: // statements within triggers. We make a specific error message for this
1239: // since it is an exception to the default grammar rules.
1240: //
1241: tridxby ::= .
1242: tridxby ::= INDEXED BY nm. {
1243: sqlite3ErrorMsg(pParse,
1244: "the INDEXED BY clause is not allowed on UPDATE or DELETE statements "
1245: "within triggers");
1246: }
1247: tridxby ::= NOT INDEXED. {
1248: sqlite3ErrorMsg(pParse,
1249: "the NOT INDEXED clause is not allowed on UPDATE or DELETE statements "
1250: "within triggers");
1251: }
1252:
1253:
1254:
1255: %type trigger_cmd {TriggerStep*}
1256: %destructor trigger_cmd {sqlite3DeleteTriggerStep(pParse->db, $$);}
1257: // UPDATE
1258: trigger_cmd(A) ::=
1259: UPDATE orconf(R) trnm(X) tridxby SET setlist(Y) where_opt(Z).
1260: { A = sqlite3TriggerUpdateStep(pParse->db, &X, Y, Z, R); }
1261:
1262: // INSERT
1263: trigger_cmd(A) ::=
1264: insert_cmd(R) INTO trnm(X) inscollist_opt(F) VALUES LP itemlist(Y) RP.
1265: {A = sqlite3TriggerInsertStep(pParse->db, &X, F, Y, 0, R);}
1266:
1267: trigger_cmd(A) ::= insert_cmd(R) INTO trnm(X) inscollist_opt(F) select(S).
1268: {A = sqlite3TriggerInsertStep(pParse->db, &X, F, 0, S, R);}
1269:
1270: // DELETE
1271: trigger_cmd(A) ::= DELETE FROM trnm(X) tridxby where_opt(Y).
1272: {A = sqlite3TriggerDeleteStep(pParse->db, &X, Y);}
1273:
1274: // SELECT
1275: trigger_cmd(A) ::= select(X). {A = sqlite3TriggerSelectStep(pParse->db, X); }
1276:
1277: // The special RAISE expression that may occur in trigger programs
1278: expr(A) ::= RAISE(X) LP IGNORE RP(Y). {
1279: A.pExpr = sqlite3PExpr(pParse, TK_RAISE, 0, 0, 0);
1280: if( A.pExpr ){
1281: A.pExpr->affinity = OE_Ignore;
1282: }
1283: A.zStart = X.z;
1284: A.zEnd = &Y.z[Y.n];
1285: }
1286: expr(A) ::= RAISE(X) LP raisetype(T) COMMA nm(Z) RP(Y). {
1287: A.pExpr = sqlite3PExpr(pParse, TK_RAISE, 0, 0, &Z);
1288: if( A.pExpr ) {
1289: A.pExpr->affinity = (char)T;
1290: }
1291: A.zStart = X.z;
1292: A.zEnd = &Y.z[Y.n];
1293: }
1294: %endif !SQLITE_OMIT_TRIGGER
1295:
1296: %type raisetype {int}
1297: raisetype(A) ::= ROLLBACK. {A = OE_Rollback;}
1298: raisetype(A) ::= ABORT. {A = OE_Abort;}
1299: raisetype(A) ::= FAIL. {A = OE_Fail;}
1300:
1301:
1302: //////////////////////// DROP TRIGGER statement //////////////////////////////
1303: %ifndef SQLITE_OMIT_TRIGGER
1304: cmd ::= DROP TRIGGER ifexists(NOERR) fullname(X). {
1305: sqlite3DropTrigger(pParse,X,NOERR);
1306: }
1307: %endif !SQLITE_OMIT_TRIGGER
1308:
1309: //////////////////////// ATTACH DATABASE file AS name /////////////////////////
1310: %ifndef SQLITE_OMIT_ATTACH
1311: cmd ::= ATTACH database_kw_opt expr(F) AS expr(D) key_opt(K). {
1312: sqlite3Attach(pParse, F.pExpr, D.pExpr, K);
1313: }
1314: cmd ::= DETACH database_kw_opt expr(D). {
1315: sqlite3Detach(pParse, D.pExpr);
1316: }
1317:
1318: %type key_opt {Expr*}
1319: %destructor key_opt {sqlite3ExprDelete(pParse->db, $$);}
1320: key_opt(A) ::= . { A = 0; }
1321: key_opt(A) ::= KEY expr(X). { A = X.pExpr; }
1322:
1323: database_kw_opt ::= DATABASE.
1324: database_kw_opt ::= .
1325: %endif SQLITE_OMIT_ATTACH
1326:
1327: ////////////////////////// REINDEX collation //////////////////////////////////
1328: %ifndef SQLITE_OMIT_REINDEX
1329: cmd ::= REINDEX. {sqlite3Reindex(pParse, 0, 0);}
1330: cmd ::= REINDEX nm(X) dbnm(Y). {sqlite3Reindex(pParse, &X, &Y);}
1331: %endif SQLITE_OMIT_REINDEX
1332:
1333: /////////////////////////////////// ANALYZE ///////////////////////////////////
1334: %ifndef SQLITE_OMIT_ANALYZE
1335: cmd ::= ANALYZE. {sqlite3Analyze(pParse, 0, 0);}
1336: cmd ::= ANALYZE nm(X) dbnm(Y). {sqlite3Analyze(pParse, &X, &Y);}
1337: %endif
1338:
1339: //////////////////////// ALTER TABLE table ... ////////////////////////////////
1340: %ifndef SQLITE_OMIT_ALTERTABLE
1341: cmd ::= ALTER TABLE fullname(X) RENAME TO nm(Z). {
1342: sqlite3AlterRenameTable(pParse,X,&Z);
1343: }
1344: cmd ::= ALTER TABLE add_column_fullname ADD kwcolumn_opt column(Y). {
1345: sqlite3AlterFinishAddColumn(pParse, &Y);
1346: }
1347: add_column_fullname ::= fullname(X). {
1348: pParse->db->lookaside.bEnabled = 0;
1349: sqlite3AlterBeginAddColumn(pParse, X);
1350: }
1351: kwcolumn_opt ::= .
1352: kwcolumn_opt ::= COLUMNKW.
1353: %endif SQLITE_OMIT_ALTERTABLE
1354:
1355: //////////////////////// CREATE VIRTUAL TABLE ... /////////////////////////////
1356: %ifndef SQLITE_OMIT_VIRTUALTABLE
1357: cmd ::= create_vtab. {sqlite3VtabFinishParse(pParse,0);}
1358: cmd ::= create_vtab LP vtabarglist RP(X). {sqlite3VtabFinishParse(pParse,&X);}
1359: create_vtab ::= createkw VIRTUAL TABLE nm(X) dbnm(Y) USING nm(Z). {
1360: sqlite3VtabBeginParse(pParse, &X, &Y, &Z);
1361: }
1362: vtabarglist ::= vtabarg.
1363: vtabarglist ::= vtabarglist COMMA vtabarg.
1364: vtabarg ::= . {sqlite3VtabArgInit(pParse);}
1365: vtabarg ::= vtabarg vtabargtoken.
1366: vtabargtoken ::= ANY(X). {sqlite3VtabArgExtend(pParse,&X);}
1367: vtabargtoken ::= lp anylist RP(X). {sqlite3VtabArgExtend(pParse,&X);}
1368: lp ::= LP(X). {sqlite3VtabArgExtend(pParse,&X);}
1369: anylist ::= .
1370: anylist ::= anylist LP anylist RP.
1371: anylist ::= anylist ANY.
1372: %endif SQLITE_OMIT_VIRTUALTABLE
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>