sql: refactoring (SingleIn -> SingleText)
[sqlgg.git] / lib / syntax.ml
blob0ab9a30bcd9d9e8f4faeef3d9f691e0ab4283611
1 (** SQL syntax and RA *)
3 open Printf
4 open ExtLib
5 open Prelude
6 open Sql
8 let debug = ref false
10 type env = {
11 tables : Tables.table list;
12 schema : Schema.t;
13 insert_schema : Schema.t;
16 let empty_env = { tables = []; schema = []; insert_schema = []; }
18 let flat_map f l = List.flatten (List.map f l)
20 let schema_of tables name = snd @@ Tables.get_from tables name
22 let get_or_failwith = function `Error s -> failwith s | `Ok t -> t
24 let values_or_all table names =
25 let schema = Tables.get_schema table in
26 match names with
27 | Some names -> Schema.project names schema
28 | None -> schema
30 let rec get_params_q (e:expr_q) =
31 let rec loop acc e =
32 match e with
33 | `Param p -> Single p::acc
34 | `Inparam p -> SingleText p::acc
35 | `Func (_,l) -> List.fold_left loop acc l
36 | `Value _ -> acc
37 | `Choice (p,l) -> Choice (p, List.map (fun (n,e) -> Simple (n, Option.map get_params_q e)) l) :: acc
39 loop [] e |> List.rev
41 let list_same l =
42 match l with
43 | [] -> None
44 | x::xs -> if List.for_all (fun y -> x = y) xs then Some x else None
46 let rec is_grouping = function
47 | Value _
48 | Param _
49 | Column _
50 | Select _
51 | Inparam _
52 | Inserted _ -> false
53 | Choices (p,l) ->
54 begin match list_same @@ List.map (fun (_,expr) -> Option.map_default is_grouping false expr) l with
55 | None -> failed ~at:p.pos "inconsistent grouping in choice branches"
56 | Some v -> v
57 end
58 | Fun (func,args) ->
59 (* grouping function of zero or single parameter or function on grouping result *)
60 (Type.is_grouping func && List.length args <= 1) || List.exists is_grouping args
62 let exists_grouping columns =
63 List.exists (function Expr (e,_) -> is_grouping e | All | AllOf _ -> false) columns
65 let cross = List.fold_left Schema.cross []
67 (* all columns from tables, without duplicates *)
68 (* FIXME check type of duplicates *)
69 let all_columns = Schema.make_unique $ cross
70 let all_tbl_columns = all_columns $ List.map snd
72 let resolve_column tables schema {cname;tname} =
73 Schema.find (Option.map_default (schema_of tables) schema tname) cname
75 (* HACK hint expression to unify with the column type *)
76 let rec hint attr expr =
77 (* associate parameter with column *)
78 let expr = match expr with Param p -> Param { p with attr = Some attr } | e -> e in
79 (* go one level deep into choices *)
80 match expr with
81 | Choices (n,l) -> Choices (n, List.map (fun (n,e) -> n, Option.map (hint attr) e) l)
82 | _ -> Fun (F (Var 0, [Var 0; Var 0]), [Value attr.domain;expr])
84 let resolve_column_assignments tables l =
85 let all = all_tbl_columns tables in
86 l |> List.map begin fun (col,expr) ->
87 let attr = resolve_column tables all col in
88 hint attr expr
89 end
91 let get_columns_schema tables l =
92 let all = all_tbl_columns tables in
93 (* FIXME col_name *)
94 l |> List.map (fun col -> { (resolve_column tables all col) with name = col.cname })
96 (** replace each name reference (Column, Inserted, etc) with Value of corresponding type *)
97 let rec resolve_columns env expr =
98 if !debug then
99 begin
100 eprintf "\nRESOLVE COLUMNS %s\n%!" (expr_to_string expr);
101 eprintf "schema: "; Sql.Schema.print env.schema;
102 Tables.print stderr env.tables;
103 end;
104 let rec each e =
105 match e with
106 | Value x -> `Value x
107 | Column col -> `Value (resolve_column env.tables env.schema col).domain
108 | Inserted name ->
109 let attr = try Schema.find env.insert_schema name with Schema.Error (_,s) -> fail "for inserted values : %s" s in
110 `Value attr.domain
111 | Param x -> `Param x
112 | Inparam x -> `Inparam x
113 | Choices (n,l) -> `Choice (n, List.map (fun (n,e) -> n, Option.map each e) l)
114 | Fun (r,l) ->
115 `Func (r,List.map each l)
116 | Select (select, usage) ->
117 let as_params p =
118 List.map
119 (function
120 | Single p -> `Param p
121 | SingleText p -> failed ~at:p.id.pos "FIXME as_params in SingleText"
122 | Choice (p,_) -> failed ~at:p.pos "FIXME as_params in Choice")
123 p in
124 let (schema,p,_) = eval_select_full env select in
125 match schema, usage with
126 | [ {domain;_} ], `AsValue -> `Func (Type.Ret domain, as_params p)
127 | s, `AsValue -> raise (Schema.Error (s, "only one column allowed for SELECT operator in this expression"))
128 | _, `Exists -> `Func (Type.Ret Any, as_params p)
130 each expr
132 (** assign types to parameters where possible *)
133 and assign_types expr =
134 let option_split = function None -> None, None | Some (x,y) -> Some x, Some y in
135 let rec typeof (e:expr_q) = (* FIXME simplify *)
136 match e with
137 | `Value t -> e, `Ok t
138 | `Param p -> e, `Ok p.typ
139 | `Inparam p -> e, `Ok (Tuple p.typ)
140 | `Choice (n,l) ->
141 let (e,t) = List.split @@ List.map (fun (_,e) -> option_split @@ Option.map typeof e) l in
142 let t =
143 match List.map get_or_failwith @@ List.filter_map identity t with
144 | [] -> assert false
145 | t::ts -> List.fold_left (fun acc t -> match acc with None -> None | Some prev -> Type.common_subtype prev t) (Some t) ts
147 let t = match t with None -> `Error "no common subtype for all choice branches" | Some t -> `Ok t in
148 `Choice (n, List.map2 (fun (n,_) e -> n,e) l e), t
149 | `Func (func,params) ->
150 let open Type in
151 let (params,types) = params |> List.map typeof |> List.split in
152 let types = List.map get_or_failwith types in
153 let show () =
154 sprintf "%s applied to (%s)"
155 (string_of_func func)
156 (String.concat ", " @@ List.map to_string types)
158 let func =
159 match func with
160 | Multi (ret,each_arg) -> F (ret, List.map (fun _ -> each_arg) types)
161 | x -> x
163 let (ret,inferred_params) = match func, types with
164 | Multi _, _ -> assert false (* rewritten into F above *)
165 | Agg, [typ]
166 | Group typ, _ -> typ, types
167 | Agg, _ -> fail "cannot use this grouping function with %d parameters" (List.length types)
168 | F (_, args), _ when List.length args <> List.length types -> fail "wrong number of arguments : %s" (show ())
169 | F (ret, args), _ ->
170 let typevar = Hashtbl.create 10 in
171 let l = List.map2 begin fun arg typ ->
172 match arg with
173 | Typ arg -> common_type arg typ
174 | Var i ->
175 let arg =
176 match Hashtbl.find typevar i with
177 | exception Not_found -> Hashtbl.replace typevar i typ; typ
178 | t -> t
180 (* prefer more precise type *)
181 if arg = Type.Any then Hashtbl.replace typevar i typ;
182 common_type arg typ
183 end args types
185 let convert = function Typ t -> t | Var i -> Hashtbl.find typevar i in
186 if List.fold_left (&&) true l then
187 convert ret, List.map convert args
188 else
189 fail "types do not match : %s" (show ())
190 | InF (lhs, rhs), _ ->
191 let typevar = Hashtbl.create 10 in
192 let l = List.map2 begin fun arg typ ->
193 match arg with
194 | Typ arg -> common_type arg typ
195 | Var i ->
196 let arg =
197 match Hashtbl.find typevar i with
198 | exception Not_found -> Hashtbl.replace typevar i typ; typ
199 | t -> t
201 (* prefer more precise type *)
202 begin match arg with
203 | Type.Any -> Hashtbl.replace typevar i typ
204 | _ -> ()
205 end;
206 common_type arg typ ||
207 match typ with Tuple _ -> true | _ -> false
208 end [lhs; rhs] types
210 let convert = function Typ t -> t | Var i -> Hashtbl.find typevar i in
211 if List.fold_left (&&) true l then begin
212 let concrete_typ = convert lhs in
213 Bool, [ concrete_typ; Tuple concrete_typ ]
214 end else
215 fail "types do not match : %s" (show ())
216 | Ret Any, _ -> (* lame *)
217 begin match List.filter ((<>) Any) types with
218 | [] -> Any, types
219 (* make a best guess, return type same as for parameters when all of single type *)
220 | h::tl when List.for_all (matches h) tl -> h, List.map (fun _ -> h) types
221 (* "expand" to floats, when all parameters numeric and above rule didn't match *)
222 | l when List.for_all (function Int | Float -> true | _ -> false) l -> Float, List.map (function Any -> Float | x -> x) types
223 | _ -> Any, types
225 | Ret ret, _ -> ret, types (* ignoring arguments FIXME *)
227 let assign inferred x =
228 match x with
229 | `Param { id; typ = Any; attr } -> `Param (new_param ?attr id inferred)
230 | `Inparam { id; typ = Any; attr } -> `Inparam (new_param ?attr id inferred)
231 | x -> x
233 `Func (func,(List.map2 assign inferred_params params)), `Ok ret
235 typeof expr
237 and resolve_types env expr =
238 let expr = resolve_columns env expr in
240 let (expr',t as r) = assign_types expr in
241 if !debug then eprintf "resolved types %s : %s\n%!" (show_expr_q expr') (Type.to_string @@ get_or_failwith t);
243 with
244 exn ->
245 eprintfn "resolve_types failed with %s at:" (Printexc.to_string exn);
246 eprintfn "%s" (show_expr_q expr);
247 raise exn
249 and infer_schema env columns =
250 (* let all = tables |> List.map snd |> List.flatten in *)
251 let resolve1 = function
252 | All -> env.schema
253 | AllOf t -> schema_of env.tables t
254 | Expr (e,name) ->
255 let col =
256 match e with
257 | Column col -> resolve_column env.tables env.schema col
258 | _ -> make_attribute "" (resolve_types env e |> snd |> get_or_failwith) Constraints.empty
260 let col = Option.map_default (fun n -> {col with name = n}) col name in
261 [ col ]
263 flat_map resolve1 columns
265 and get_params env e = e |> resolve_types env |> fst |> get_params_q
268 let _ =
269 let e = Sub [Value Type.Text; Param (Next,None); Sub []; Param (Named "ds", Some Type.Int);] in
270 e |> get_params |> to_string |> print_endline
273 and params_of_columns env =
274 let get = function
275 | All | AllOf _ -> []
276 | Expr (e,_) -> get_params env e
278 flat_map get
280 and get_params_opt env = function
281 | Some x -> get_params env x
282 | None -> []
284 and get_params_l env l = flat_map (get_params env) l
286 and do_join (env,params) ((schema1,params1,_tables),kind) =
287 let schema = match kind with
288 | `Cross
289 | `Search _
290 | `Default -> Schema.cross env.schema schema1
291 | `Natural -> Schema.natural env.schema schema1
292 | `Using l -> Schema.join_using l env.schema schema1
294 let env = { env with schema } in
295 let p = match kind with
296 | `Cross | `Default | `Natural | `Using _ -> []
297 | `Search e -> get_params env e (* TODO should use final schema (same as tables)? *)
299 env, params @ params1 @ p
301 and join env ((schema,p0,ts0),joins) =
302 assert (env.schema = []);
303 let all_tables = List.flatten (ts0 :: List.map (fun ((_,_,ts),_) -> ts) joins) in
304 let env = { env with tables = env.tables @ all_tables; schema; } in
305 List.fold_left do_join (env, p0) joins
307 and params_of_assigns env ss =
308 let exprs = resolve_column_assignments env.tables ss in
309 get_params_l env exprs
311 and params_of_order order final_schema tables =
312 let (orders,directions) = List.split order in
313 let directions = List.filter_map (function None | Some `Fixed -> None | Some (`Param p) -> Some (Choice (p,[Verbatim ("ASC","ASC");Verbatim ("DESC","DESC")]))) directions in
314 get_params_l { tables; schema=(final_schema :: (List.map snd tables) |> all_columns); insert_schema = []; } orders
316 directions
318 and ensure_simple_expr = function
319 | Value x -> `Value x
320 | Param x -> `Param x
321 | Inparam x -> `Inparam x
322 | Choices (p,_) -> failed ~at:p.pos "ensure_simple_expr Choices TBD"
323 | Column _ | Inserted _ -> failwith "Not a simple expression"
324 | Fun (func,_) when Type.is_grouping func -> failwith "Grouping function not allowed in simple expression"
325 | Fun (x,l) -> `Func (x,List.map ensure_simple_expr l) (* FIXME *)
326 | Select _ -> failwith "not implemented : ensure_simple_expr for SELECT"
328 and eval_nested env nested =
329 (* nested selects generate new fresh schema in scope, cannot refer to outer schema,
330 but can refer to attributes of tables through `tables` *)
331 let env = { env with schema = [] } in
332 match nested with
333 | Some (t,l) -> join env (resolve_source env t, List.map (fun (x,k) -> resolve_source env x, k) l)
334 | None -> env, []
336 and eval_select env { columns; from; where; group; having; } =
337 let (env,p2) = eval_nested env from in
338 let cardinality =
339 if from = None then (if where = None then `One else `Zero_one)
340 else if group = [] && exists_grouping columns then `One
341 else `Nat
343 let final_schema = infer_schema env columns in
344 (* use schema without aliases here *)
345 let p1 = params_of_columns env columns in
346 let env = Schema.{ env with schema = cross env.schema final_schema |> make_unique } in (* enrich schema in scope with aliases *)
347 let p3 = get_params_opt env where in
348 let p4 = get_params_l env group in
349 let p5 = get_params_opt env having in
350 (final_schema, p1 @ p2 @ p3 @ p4 @ p5, env.tables, cardinality)
352 (** @return final schema, params and tables that can be referenced by outside scope *)
353 and resolve_source env (x,alias) =
354 match x with
355 | `Select select ->
356 let (s,p,_) = eval_select_full env select in
357 s, p, (match alias with None -> [] | Some name -> [name,s])
358 | `Nested s ->
359 let (env,p) = eval_nested env (Some s) in
360 let s = infer_schema env [All] in
361 if alias <> None then failwith "No alias allowed on nested tables";
362 s, p, env.tables
363 | `Table s ->
364 let (name,s) = Tables.get s in
365 s, [], [Option.default name alias, s]
367 and eval_select_full env { select=(select,other); order; limit; } =
368 let (s1,p1,tbls,cardinality) = eval_select env select in
369 let (s2l,p2l) = List.split (List.map (fun (s,p,_,_) -> s,p) @@ List.map (eval_select env) other) in
370 if false then
371 eprintf "cardinality=%s other=%u\n%!"
372 (Stmt.cardinality_to_string cardinality)
373 (List.length other);
374 let cardinality = if other = [] then cardinality else `Nat in
375 (* ignoring tables in compound statements - they cannot be used in ORDER BY *)
376 let final_schema = List.fold_left Schema.compound s1 s2l in
377 let p3 = params_of_order order final_schema tbls in
378 let (p4,limit1) = match limit with Some (p,x) -> List.map (fun p -> Single p) p, x | None -> [],false in
379 (* Schema.check_unique schema; *)
380 let cardinality =
381 if limit1 && cardinality = `Nat then `Zero_one
382 else cardinality in
383 final_schema,(p1@(List.flatten p2l)@p3@p4 : var list), Stmt.Select cardinality
386 let update_tables sources ss w =
387 let schema = cross @@ (List.map (fun (s,_,_) -> s) sources) in
388 let p0 = List.flatten @@ List.map (fun (_,p,_) -> p) sources in
389 let tables = List.flatten @@ List.map (fun (_,_,ts) -> ts) sources in (* TODO assert equal duplicates if not unique *)
390 let env = { tables; schema; insert_schema=get_columns_schema tables (List.map fst ss); } in
391 let p1 = params_of_assigns env ss in
392 let p2 = get_params_opt env w in
393 p0 @ p1 @ p2
395 let annotate_select select types =
396 let (select1,compound) = select.select in
397 let rec loop acc cols types =
398 match cols, types with
399 | [], [] -> List.rev acc
400 | (All | AllOf _) :: _, _ -> failwith "Asterisk not supported"
401 | Expr (e,name) :: cols, t :: types -> loop (Expr (Fun (F (Typ t, [Typ t]), [e]), name) :: acc) cols types
402 | _, [] | [], _ -> failwith "Select cardinality doesn't match Insert"
404 { select with select = { select1 with columns = loop [] select1.columns types }, compound }
406 let eval (stmt:Sql.stmt) =
407 let open Stmt in
408 match stmt with
409 | Create (name,`Schema schema) ->
410 Tables.add (name,schema);
411 ([],[],Create name)
412 | Create (name,`Select select) ->
413 let (schema,params,_) = eval_select_full empty_env select in
414 Tables.add (name,schema);
415 ([],params,Create name)
416 | Alter (name,actions) ->
417 List.iter (function
418 | `Add (col,pos) -> Tables.alter_add name col pos
419 | `Drop col -> Tables.alter_drop name col
420 | `Change (oldcol,col,pos) -> Tables.alter_change name oldcol col pos
421 | `RenameColumn (oldcol,newcol) -> Tables.rename_column name oldcol newcol
422 | `RenameTable new_name -> Tables.rename name new_name
423 | `RenameIndex _ -> () (* indices are not tracked yet *)
424 | `None -> ()) actions;
425 ([],[],Alter [name])
426 | Rename l ->
427 List.iter (fun (o,n) -> Tables.rename o n) l;
428 ([], [], Alter (List.map fst l)) (* to have sensible target for gen_xml *)
429 | Drop name ->
430 Tables.drop name;
431 ([],[],Drop name)
432 | CreateIndex (name,table,cols) ->
433 Sql.Schema.project cols (Tables.get_schema table) |> ignore; (* just check *)
434 [],[],CreateIndex name
435 | Insert { target=table; action=`Values (names, values); on_duplicate; } ->
436 let expect = values_or_all table names in
437 let env = { tables = [Tables.get table]; schema = Tables.get_schema table; insert_schema = expect; } in
438 let params, inferred = match values with
439 | None -> [], Some (Values, expect)
440 | Some values ->
441 let vl = List.map List.length values in
442 let cl = List.length expect in
443 if List.exists (fun n -> n <> cl) vl then
444 fail "Expecting %u expressions in every VALUES tuple" cl;
445 let assigns = values |>
446 List.map begin fun tuple ->
447 (* pair up columns with inserted values *)
448 List.combine (List.map (fun a -> {cname=a.name; tname=None}) expect) tuple
449 (* resolve DEFAULTs *)
450 |> List.map (function (col,`Expr e) -> col, e | (col,`Default) -> col, Fun (Type.identity, [Column col]))
453 params_of_assigns env (List.concat assigns), None
455 let params2 = params_of_assigns env (Option.default [] on_duplicate) in
456 [], params @ params2, Insert (inferred,table)
457 | Insert { target=table; action=`Select (names, select); on_duplicate; } ->
458 let expect = values_or_all table names in
459 let env = { tables = [Tables.get table]; schema = Tables.get_schema table; insert_schema = expect; } in
460 let select = annotate_select select (List.map (fun a -> a.domain) expect) in
461 let (schema,params,_) = eval_select_full env select in
462 ignore (Schema.compound expect schema); (* test equal types once more (not really needed) *)
463 let params2 = params_of_assigns env (Option.default [] on_duplicate) in
464 [], params @ params2, Insert (None,table)
465 | Insert { target=table; action=`Set ss; on_duplicate; } ->
466 let expect = values_or_all table (Option.map (List.map (function ({cname; tname=None},_) -> cname | _ -> assert false)) ss) in
467 let env = { tables = [Tables.get table]; schema = Tables.get_schema table; insert_schema = expect; } in
468 let (params,inferred) = match ss with
469 | None -> [], Some (Assign, Tables.get_schema table)
470 | Some ss -> params_of_assigns env ss, None
472 let params2 = params_of_assigns env (Option.default [] on_duplicate) in
473 [], params @ params2, Insert (inferred,table)
474 | Delete (table, where) ->
475 let t = Tables.get table in
476 let p = get_params_opt { tables=[t]; schema=snd t; insert_schema=[]; } where in
477 [], p, Delete table
478 | Set (_name, e) ->
479 let p = match e with
480 | Column _ -> [] (* this is not column but some db-specific identifier *)
481 | _ -> get_params_q (ensure_simple_expr e)
483 [], p, Other
484 | Update (table,ss,w,o,lim) ->
485 let t = Tables.get table in
486 let params = update_tables [snd t,[],[t]] ss w in
487 let p3 = params_of_order o [] [t] in
488 [], params @ p3 @ (List.map (fun p -> Single p) lim), Update (Some table)
489 | UpdateMulti (tables,ss,w) ->
490 let sources = List.map (resolve_source empty_env) tables in
491 let params = update_tables sources ss w in
492 [], params, Update None
493 | Select select -> eval_select_full empty_env select
494 | CreateRoutine (name,_,_) ->
495 [], [], CreateRoutine name
497 (* FIXME unify each choice separately *)
498 let unify_params l =
499 let h = Hashtbl.create 10 in
500 let h_choices = Hashtbl.create 10 in
501 let check_choice_name p =
502 match p.label with
503 | None -> () (* unique *)
504 | Some n when Hashtbl.mem h_choices n -> failed ~at:p.pos "sharing choices not implemented"
505 | Some n -> Hashtbl.add h_choices n ()
507 let remember name t =
508 match name with
509 | None -> () (* anonymous ie non-shared *)
510 | Some name ->
511 match Hashtbl.find h name with
512 | exception _ -> Hashtbl.add h name t
513 | t' ->
514 match Sql.Type.common_subtype t t' with
515 | Some x -> Hashtbl.replace h name x
516 | None -> fail "incompatible types for parameter %S : %s and %s" name (Type.show t) (Type.show t')
518 let rec traverse = function
519 | Single { id; typ; attr=_ } -> remember id.label typ
520 | SingleText { id; typ; _ } -> remember id.label typ
521 | Choice (p,l) -> check_choice_name p; List.iter (function Simple (_,l) -> Option.may (List.iter traverse) l | Verbatim _ -> ()) l
523 let rec map = function
524 | Single { id; typ; attr } -> Single (new_param id ?attr (match id.label with None -> typ | Some name -> try Hashtbl.find h name with _ -> assert false))
525 | SingleText { id; typ; attr } -> SingleText (new_param id ?attr (match id.label with None -> typ | Some name -> try Hashtbl.find h name with _ -> assert false))
526 | Choice (p, l) -> Choice (p, List.map (function Simple (n,l) -> Simple (n, Option.map (List.map map) l) | Verbatim _ as v -> v) l)
528 List.iter traverse l;
529 List.map map l
531 let is_alpha = function
532 | 'a'..'z' -> true
533 | 'A'..'Z' -> true
534 | _ -> false
536 let common_prefix = function
537 | [] -> 0
538 | x::_ as l ->
539 let rec loop i =
540 if String.length x <= i then i
541 else
542 if List.for_all (fun s -> i < String.length s && s.[i] = x.[i]) l then
543 loop (i+1)
544 else
547 let i = loop 0 in
548 (* do not allow empty names or starting not with alpha *)
549 if List.exists (fun s -> i = String.length s || not (is_alpha s.[i])) l then 0 else i
551 (* fill inferred sql for VALUES or SET *)
552 let complete_sql kind sql =
553 match kind with
554 | Stmt.Insert (Some (kind,schema), _) ->
555 let (pre,each,post) = match kind with
556 | Values -> "(", (fun _ -> ""), ")"
557 | Assign -> "", (fun name -> name ^" = "), ""
559 let module B = Buffer in
560 let b = B.create 100 in
561 B.add_string b sql;
562 B.add_string b " ";
563 B.add_string b pre;
564 let params = ref [] in
565 let first = common_prefix @@ List.map (fun attr -> attr.Sql.name) schema in
566 schema |> List.iter (fun attr ->
567 if !params <> [] then B.add_string b ",";
568 let attr_ref_prefix = each attr.Sql.name in
569 let attr_name = String.slice ~first attr.Sql.name in
570 let attr_ref = "@" ^ attr_name in
571 let pos_start = B.length b + String.length attr_ref_prefix in
572 let pos_end = pos_start + String.length attr_ref in
573 let param = Single (new_param ~attr {label=Some attr_name; pos=(pos_start,pos_end)} attr.domain) in
574 B.add_string b attr_ref_prefix;
575 B.add_string b attr_ref;
576 tuck params param;
578 B.add_string b post;
579 (B.contents b, List.rev !params)
580 | _ -> (sql,[])
582 let parse sql =
583 let (schema,p1,kind) = eval @@ Parser.parse_stmt sql in
584 let (sql,p2) = complete_sql kind sql in
585 (sql, schema, unify_params (p1 @ p2), kind)