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