stay compatible with ocaml >= 3.12.1
[sqlgg.git] / lib / sql_parser.mly
bloba301c7cc679df6d63912e6cb03deabe436f935d3
1 /*
2   Simple SQL parser
3 */
6 %{
7   open Printf
8   open Sql.Constraint
9   open Sql.Type
10   open Stmt
11   open Syntax
12   open Prelude
14   let params_of select = List.map (fun x -> `Param x) (snd select)
16   let select_value select =
17     let (s,_) = select in
18     if (List.length s <> 1) then
19       raise (RA.Schema.Error (s,"only one column allowed for SELECT operator in this expression"));
20     params_of select
22   let values_or_all table names =
23     let schema = Tables.get_schema table in
24     match names with
25     | Some names -> RA.Schema.project names schema
26     | None -> schema
28   let update_tables tables ss w =
29     let (tables,params) = List.split tables in
30     let p1 = Syntax.params_of_assigns tables ss in
31     let p2 = get_params_opt tables (Syntax.all_tbl_columns tables) w in
32     (List.flatten params) @ p1 @ p2
34   (* preserve order *)
35   let limit l =
36     let param = function
37       | _, `Const _ -> None
38       | x, `Param (None,pos) -> Some ((Some (match x with `Limit -> "limit" | `Offset -> "offset"),pos),Int)
39       | _, `Param p -> Some (p,Int)
40     in
41     list_filter_map param l, List.mem (`Limit,`Const 1) l
45 %token <int> INTEGER
46 %token <string> IDENT TEXT BLOB
47 %token <float> FLOAT
48 %token <Stmt.param_id> PARAM
49 %token <Sql.Type.t * bool> FUNCTION /* return type * is grouping function? */
50 %token LPAREN RPAREN COMMA EOF DOT NULL
51 %token CONFLICT_ALGO
52 %token SELECT INSERT OR INTO CREATE UPDATE VIEW TABLE VALUES WHERE ASTERISK DISTINCT ALL ANY SOME
53        LIMIT ORDER BY DESC ASC EQUAL DELETE FROM DEFAULT OFFSET SET JOIN LIKE_OP LIKE
54        EXCL TILDE NOT TEST_NULL BETWEEN AND ESCAPE USING UNION EXCEPT INTERSECT AS
55        CONCAT_OP JOIN_TYPE1 JOIN_TYPE2 NATURAL CROSS REPLACE IN GROUP HAVING
56        UNIQUE PRIMARY KEY FOREIGN AUTOINCREMENT ON CONFLICT TEMPORARY IF EXISTS
57        PRECISION UNSIGNED ZEROFILL VARYING CHARSET NATIONAL ASCII UNICODE COLLATE BINARY CHARACTER
58        DATETIME_FUNC DATE TIME TIMESTAMP ALTER ADD COLUMN CASCADE RESTRICT DROP
59        GLOBAL LOCAL VALUE REFERENCES CHECK CONSTRAINT IGNORED AFTER INDEX FULLTEXT FIRST
60        CASE WHEN THEN ELSE END CHANGE MODIFY DELAYED ENUM
61 %token NUM_DIV_OP NUM_BIT_OP NUM_EQ_OP NUM_CMP_OP PLUS MINUS
62 %token T_INTEGER T_BLOB T_TEXT T_FLOAT T_BOOLEAN T_DATETIME
65 %left COMMA_JOIN
66 %left JOIN_JOIN
68 (* FIXME precedence of COMMA and JOIN *)
70 %left TEST_NULL
71 %left OR
72 %left AND
73 %nonassoc EQUAL NUM_EQ_OP
74 %nonassoc NUM_CMP_OP
75 %nonassoc NUM_BIT_OP
76 %left PLUS MINUS
77 %left ASTERISK NUM_DIV_OP
78 %left CONCAT_OP
79 %nonassoc UNARY_MINUS
81 %type <Syntax.expr> expr
83 %start <RA.Schema.t * Stmt.params * Stmt.kind> input
87 input: statement EOF { $1 }
89 if_not_exists: IF NOT EXISTS { }
90 if_exists: IF EXISTS {}
91 temporary: either(GLOBAL,LOCAL)? TEMPORARY { }
93 statement: CREATE ioption(temporary) TABLE ioption(if_not_exists) name=IDENT schema=table_definition
94               {
95                 Tables.add (name,schema);
96                 ([],[],Create name)
97               }
98          | ALTER TABLE name=table_name actions=commas(alter_action)
99               {
100                 List.iter (function
101                 | `Add (col,pos) -> Tables.alter_add name col pos
102                 | `Drop col -> Tables.alter_drop name col
103                 | `Change (oldcol,col,pos) -> Tables.alter_change name oldcol col pos
104                 | `None -> ()) actions;
105                 ([],[],Alter name)
106               }
107          | DROP TABLE if_exists? name=IDENT
108               {
109                 Tables.drop name;
110                 ([],[],Drop name)
111               }
112          | CREATE either(TABLE,VIEW) name=IDENT AS select=maybe_parenth(select_stmt)
113               {
114                 let (s,p) = select in
115                 Tables.add (name,s);
116                 ([],p,Create name)
117               }
118          | CREATE UNIQUE? INDEX if_not_exists? name=table_name
119                 ON table=table_name cols=sequence(index_column)
120               {
121                 RA.Schema.project cols (Tables.get_schema table) |> ignore; (* just check *)
122                 [],[],CreateIndex name
123               }
124          | select_stmt_t { $1 }
125          | insert_cmd table=IDENT names=sequence(IDENT)? VALUES values=sequence(expr)?
126               {
127                 let expect = values_or_all table names in
128                 let params, inferred = match values with
129                 | None -> [], Some (Values, expect)
130                 | Some values ->
131                   let vl = List.length values in
132                   let cl = List.length expect in
133                   if vl <> cl then
134                     failwith (sprintf "Expected %u expressions in VALUES list, %u provided" cl vl);
135                   let assigns = List.combine (List.map (fun a -> a.RA.name, None) expect) values in
136                   Syntax.params_of_assigns [Tables.get table] assigns, None
137                 in
138                 [], params, Insert (inferred,table)
139               }
140          | insert_cmd table=IDENT names=sequence(IDENT)? select=maybe_parenth(select_stmt)
141               {
142                 let (schema,params) = select in
143                 let expect = values_or_all table names in
144                 ignore (RA.Schema.compound expect schema); (* test equal types *)
145                 [], params, Insert (None,table)
146               }
147          | insert_cmd table=IDENT SET ss=commas(set_column)?
148               {
149                 let (params,inferred) = match ss with
150                 | None -> [], Some (Assign, Tables.get_schema table)
151                 | Some ss -> Syntax.params_of_assigns [Tables.get table] ss, None
152                 in
153                 [], params, Insert (inferred,table)
154               }
155          | update_cmd table=IDENT SET ss=commas(set_column) w=where? o=loption(order) lim=loption(limit)
156               {
157                 let params = update_tables [Tables.get table,[]] ss w in
158                 let p3 = Syntax.params_of_order o [] [Tables.get table] in
159                 [], params @ p3 @ lim, Update (Some table)
160               }
161          /* http://dev.mysql.com/doc/refman/5.1/en/update.html multi-table syntax */
162          | update_cmd tables=commas(source) SET ss=commas(set_column) w=where?
163               {
164                 let params = update_tables tables ss w in
165                 [], params, Update None
166               }
167          | DELETE FROM table=IDENT w=where?
168               {
169                 let t = Tables.get table in
170                 let p = get_params_opt [t] (snd t) w in
171                 [], p, Delete table
172               }
173          | SET IDENT EQUAL e=expr
174               {
175                 let p = match e with
176                   | `Column _ -> [] (* this is not column but some db-specific identifier *)
177                   | _ -> get_params_q (ensure_simple_expr e)
178                 in
179                 [], p, Other
180               }
182 table_name: name=IDENT | IDENT DOT name=IDENT { name } (* FIXME db name *)
183 index_column: name=IDENT collate? order_type? { name }
185 table_definition: t=sequence_(column_def1) table_def_done { list_filter_map (function `Attr a -> Some a | `Constraint _ -> None) t }
186                 | LIKE name=maybe_parenth(IDENT) { Tables.get name |> snd } (* mysql *)
188 (* ugly, can you fixme? *)
189 (* ignoring everything after RPAREN (NB one look-ahead token) *)
190 table_def_done: table_def_done1 RPAREN IGNORED* { Parser_state.mode_normal () }
191 table_def_done1: { Parser_state.mode_ignore () }
193 select_stmt_t: select_core other=list(preceded(compound_op,select_core))
194                o=loption(order) lim=limit_t?
195               {
196                 let (s1,p1,tbls,cardinality) = $1 in
197                 let (s2l,p2l) = List.split (List.map (fun (s,p,_,_) -> s,p) other) in
198                 if false then
199                   eprintf "cardinality=%s other=%u\n%!"
200                           (cardinality_to_string cardinality)
201                           (List.length other);
202                 let cardinality = if other = [] then cardinality else `Nat in
203                 (* ignoring tables in compound statements - they cannot be used in ORDER BY *)
204                 let final_schema = List.fold_left RA.Schema.compound s1 s2l in
205                 let p3 = Syntax.params_of_order o final_schema tbls in
206                 let (p4,limit1) = match lim with | Some x -> x | None -> [],false in
207 (*                 RA.Schema.check_unique schema; *)
208                 let cardinality =
209                   if limit1 && cardinality = `Nat then `Zero_one
210                                                   else cardinality in
211                 final_schema,(p1@(List.flatten p2l)@p3@p4), Select cardinality
212               }
214 select_stmt: select_stmt_t { let (s,p,_) = $1 in s,p }
216 select_core: SELECT select_type? r=commas(column1)
217              f=from?
218              w=where?
219              g=loption(group)
220              h=having?
221               {
222                 let (tbls,p2,joined_schema) = match f with Some t -> Syntax.join t | None -> [], [], [] in
223                 let singlerow = g = [] && Syntax.test_all_grouping r in
224                 let singlerow2 = w = None && g = [] && Syntax.test_all_const r in
225                 let p1 = Syntax.params_of_columns tbls joined_schema r in
226                 let p3 = Syntax.get_params_opt tbls joined_schema w in
227                 let p4 = Syntax.get_params_l tbls joined_schema g in
228                 let p5 = Syntax.get_params_opt tbls joined_schema h in
229                 let cardinality = if singlerow then `One else
230                                   if singlerow2 then `Zero_one else `Nat in
231                 (Syntax.infer_schema r tbls joined_schema, p1 @ p2 @ p3 @ p4 @ p5, tbls, cardinality)
232               }
234 table_list: src=source joins=join_source* { (src,joins) }
236 join_source: NATURAL maybe_join_type JOIN src=source { src,`Natural }
237            | CROSS JOIN src=source { src,`Cross }
238            | qualified_join src=source cond=join_cond { src,cond }
240 qualified_join: COMMA | maybe_join_type JOIN { }
242 join_cond: ON e=expr { `Search e }
243          | USING l=sequence(IDENT) { `Using l }
244          | (* *) { `Default }
246 source1: IDENT { Tables.get $1,[] }
247        | LPAREN s=select_core RPAREN { let (s,p,_,_) = s in ("",s),p }
249 source: src=source1 alias=maybe_as
250     {
251       match alias with
252       | Some name -> let ((_,s),p) = src in ((name,s),p)
253       | None -> src
254     }
256 insert_cmd: INSERT DELAYED? OR? conflict_algo INTO | INSERT INTO | REPLACE INTO { }
257 update_cmd: UPDATE | UPDATE OR conflict_algo { }
258 conflict_algo: CONFLICT_ALGO | REPLACE { }
260 select_type: DISTINCT | ALL { }
262 int_or_param: i=INTEGER { `Const i }
263             | p=PARAM { `Param p }
265 limit_t: LIMIT lim=int_or_param { limit [`Limit,lim] }
266        | LIMIT ofs=int_or_param COMMA lim=int_or_param { limit [`Offset,ofs; `Limit,lim] }
267        | LIMIT lim=int_or_param OFFSET ofs=int_or_param { limit [`Limit,lim; `Offset,ofs] }
269 limit: limit_t { fst $1 }
271 order: ORDER BY l=commas(terminated(expr,order_type?)) { l }
272 order_type: DESC | ASC { }
274 from: FROM t=table_list { t }
275 where: WHERE e=expr { e }
276 group: GROUP BY l=expr_list { l }
277 having: HAVING e=expr { e }
279 column1:
280        | IDENT DOT ASTERISK { Syntax.AllOf $1 }
281        | ASTERISK { Syntax.All }
282        | e=expr m=maybe_as { Syntax.Expr (e,m) }
284 maybe_as: AS? name=IDENT { Some name }
285         | { None }
287 maybe_parenth(X): x=X | LPAREN x=X RPAREN { x }
289 alter_action: ADD COLUMN? col=maybe_parenth(column_def) pos=alter_pos { `Add (col,pos) }
290             | ADD index_type IDENT? sequence(IDENT) { `None }
291             | DROP INDEX IDENT { `None }
292             | DROP PRIMARY KEY { `None }
293             | DROP COLUMN? col=IDENT drop_behavior? { `Drop col } (* FIXME behavior? *)
294             | CHANGE COLUMN? old_name=IDENT column=column_def pos=alter_pos { `Change (old_name,column,pos) }
295             | MODIFY COLUMN? column=column_def pos=alter_pos { `Change (column.RA.name,column,pos) }
296             | SET IDENT IDENT { `None }
297 index_type: INDEX | FULLTEXT | PRIMARY KEY { }
298 alter_pos: AFTER col=IDENT { `After col }
299          | FIRST { `First }
300          | { `Default }
301 drop_behavior: CASCADE | RESTRICT { }
303 column_def: name=IDENT t=sql_type? column_def_extra*
304     { RA.attr name (match t with Some x -> x | None -> Int) }
306 column_def1: c=column_def { `Attr c }
307            | pair(CONSTRAINT,IDENT)? c=table_constraint_1 { `Constraint c }
309 on_conflict: ON CONFLICT algo=conflict_algo { algo }
310 column_def_extra: PRIMARY KEY { Some PrimaryKey }
311                 | NOT NULL { Some NotNull }
312                 | NULL { None }
313                 | UNIQUE { Some Unique }
314                 | AUTOINCREMENT { Some Autoincrement }
315                 | on_conflict { None }
316                 | CHECK LPAREN expr RPAREN { None }
317                 | DEFAULT default_value { None } (* FIXME check type with column *)
318                 | COLLATE IDENT { None }
320 default_value: single_literal_value | datetime_value { } (* sub expr ? *)
322 (* FIXME check columns *)
323 table_constraint_1:
324       | some_key IDENT? key_arg { [] }
325       | FOREIGN KEY IDENT? sequence(IDENT) REFERENCES IDENT sequence(IDENT)? { [] }
326       | CHECK LPAREN expr RPAREN { [] }
328 some_key: UNIQUE KEY? | PRIMARY? KEY | FULLTEXT KEY { }
329 key_arg: LPAREN VALUE RPAREN | sequence(IDENT) { }
331 set_column: name=attr_name EQUAL e=expr { name,e }
333 (* expr: expr1 { $1 |> Syntax.expr_to_string |> prerr_endline; $1 } *)
335 anyall: ANY | ALL | SOME { }
337 mnot(X): NOT x = X | x = X { x }
339 attr_name: name=IDENT { (name,None) }
340          | table=IDENT DOT name=IDENT
341          | IDENT DOT table=IDENT DOT name=IDENT { (name,Some table) } (* FIXME database identifier *)
343 expr:
344       expr numeric_bin_op expr %prec PLUS { `Func ((Any,false),[$1;$3]) } (* TODO default Int *)
345     | expr boolean_bin_op expr %prec AND { `Func ((Bool,false),[$1;$3]) }
346     | e1=expr comparison_op anyall? e2=expr %prec EQUAL { `Func ((Bool,false),[e1;e2]) }
347     | expr CONCAT_OP expr { `Func ((Text,false),[$1;$3]) }
348     | e1=expr mnot(like) e2=expr e3=escape?
349       { `Func ((Any,false),(list_filter_map identity [Some e1; Some e2; e3])) }
350     | unary_op expr { $2 }
351     | MINUS expr %prec UNARY_MINUS { $2 }
352     | LPAREN expr RPAREN { $2 }
353     | attr_name { `Column $1 }
354     | v=literal_value | v=datetime_value { v }
355     | e1=expr mnot(IN) l=sequence(expr) { `Func ((Any,false),e1::l) }
356     | e1=expr mnot(IN) LPAREN select=select_stmt RPAREN
357       {
358         `Func ((Any,false),e1::select_value select)
359       }
360     | e1=expr IN table=IDENT { Tables.check(table); e1 }
361     | LPAREN select=select_stmt RPAREN
362       {
363         `Func ((Any,false),select_value select)
364       }
365     | PARAM { `Param ($1,Any) }
366     | f=FUNCTION LPAREN p=func_params RPAREN { `Func (f,p) }
367     | expr TEST_NULL { $1 }
368     | expr mnot(BETWEEN) expr AND expr { `Func ((Any,false),[$1;$3;$5]) } (* TODO default Int *)
369     | mnot(EXISTS) LPAREN select=select_stmt RPAREN { `Func ((Bool,false),params_of select) }
370     | CASE e1=expr? branches=nonempty_list(case_branch) e2=preceded(ELSE,expr)? END
371       {
372         let l = function None -> [] | Some x -> [x] in
373         `Func ((Any,false),l e1 @ List.flatten branches @ l e2)
374       }
376 case_branch: WHEN e1=expr THEN e2=expr { [e1;e2] }
377 like: LIKE | LIKE_OP { }
379 datetime_value: | DATETIME_FUNC | DATETIME_FUNC LPAREN INTEGER? RPAREN { `Value Datetime }
381 literal_value:
382     | TEXT { `Value Text }
383     | BLOB { `Value Blob }
384     | INTEGER { `Value Int }
385     | FLOAT { `Value Float }
386     | DATE TEXT
387     | TIME TEXT
388     | TIMESTAMP TEXT { `Value Datetime }
389     | NULL { `Value Any } (* he he *)
391 single_literal_value:
392     | literal_value { $1 }
393     | MINUS INTEGER { `Value Int }
394     | MINUS FLOAT { `Value Float }
396 expr_list: l=commas(expr) { l }
397 func_params: expr_list { $1 }
398            | ASTERISK { [] }
399            | (* *) { [] }
400 escape: ESCAPE expr { $2 }
401 numeric_bin_op: PLUS | MINUS | ASTERISK | NUM_DIV_OP | NUM_BIT_OP { }
402 comparison_op: EQUAL | NUM_CMP_OP | NUM_EQ_OP { }
403 boolean_bin_op: AND | OR { }
405 unary_op: EXCL { }
406         | TILDE { }
407         | NOT { }
409 sql_type_flavor: T_INTEGER UNSIGNED? ZEROFILL? { Int }
410                | binary { Blob }
411                | NATIONAL? text VARYING? charset? collate? { Text }
412                | ENUM sequence(TEXT) charset? collate? { Text }
413                | T_FLOAT PRECISION? { Float }
414                | T_BOOLEAN { Bool }
415                | T_DATETIME | DATE | TIME | TIMESTAMP { Datetime }
417 binary: T_BLOB | BINARY | BINARY VARYING { }
418 text: T_TEXT | T_TEXT LPAREN INTEGER RPAREN | CHARACTER { }
420 %inline either(X,Y): X | Y { }
421 %inline commas(X): l=separated_nonempty_list(COMMA,X) { l }
422 (* (x1,x2,...,xn) *)
423 %inline sequence_(X): LPAREN l=commas(X) { l }
424 %inline sequence(X): l=sequence_(X) RPAREN { l }
426 charset: CHARSET either(IDENT,BINARY) | CHARACTER SET either(IDENT,BINARY) | ASCII | UNICODE { }
427 collate: COLLATE IDENT { }
429 sql_type: t=sql_type_flavor
430         | t=sql_type_flavor LPAREN INTEGER RPAREN UNSIGNED?
431         | t=sql_type_flavor LPAREN INTEGER COMMA INTEGER RPAREN
432         { t }
434 compound_op: UNION ALL? | EXCEPT | INTERSECT { }
436 maybe_join_type: JOIN_TYPE1? JOIN_TYPE2? { }