Skip to content

Commit

Permalink
fix whitespace
Browse files Browse the repository at this point in the history
  • Loading branch information
ygrek committed Mar 29, 2015
1 parent 2c5f37a commit dafd55e
Show file tree
Hide file tree
Showing 24 changed files with 86 additions and 100 deletions.
2 changes: 1 addition & 1 deletion cgi.f
Expand Up @@ -59,7 +59,7 @@
S" clear:left" sdiv

( << `div tag S" Output query parameters substitution :" TYPE
<<
<<
%[ `params `name $$ ]% `select atag
`input S" As is" option
`named S" Only named" option
Expand Down
5 changes: 2 additions & 3 deletions example/test.sql
Expand Up @@ -8,7 +8,7 @@ INSERT INTO test VALUES;
INSERT INTO test (name,descr) VALUES;
SELECT * FROM test WHERE name = @name LIMIT @limit;
-- [sqlgg] name=select_distinct_limit
SELECT DISTINCT *
SELECT DISTINCT *
FROM test ORDER BY id DESC LIMIT ?;
-- [sqlgg] name=Delete
DELETE FROM test WHERE id = ?;
Expand All @@ -21,10 +21,9 @@ SELECT test.id FROM test JOIN loc ON test_id = test.id;
SELECT test.id FROM test WHERE id = ? UNION SELECT test.id FROM test WHERE id = ?;
SELECT id+test_id AS x,? FROM loc ORDER BY x,?/x LIMIT ?,100;

CREATE TABLE zuzu AS
CREATE TABLE zuzu AS
SELECT test.id,@text || city AS city, name FROM loc JOIN test ON test_id=test.id;

SELECT x,z FROM (SELECT name as x,
city || ' ' || descr as "y""",
max(length(city),random(*)) as z FROM test LEFT JOIN (SELECT name AS city FROM test WHERE id=@id)) WHERE x > @xlo AND z < @zhi;

3 changes: 1 addition & 2 deletions example/test_caml.ml
Expand Up @@ -48,6 +48,5 @@ let main () =

()

let _ =
let _ =
Printexc.print main ()

3 changes: 1 addition & 2 deletions impl/sqlgg_mysql.ml
Expand Up @@ -82,7 +82,7 @@ let select db sql set_params callback =
in
loop ())

let execute db sql set_params =
let execute db sql set_params =
with_stmt db sql (fun stmt ->
let _ = set_params stmt in
if 0 <> P.real_status stmt then oops "execute : %s" sql;
Expand All @@ -95,4 +95,3 @@ let select1 db sql set_params callback =
| None -> None)

end

4 changes: 2 additions & 2 deletions impl/sqlgg_traits.ml
Expand Up @@ -49,7 +49,7 @@ module type M = sig

val no_params : statement -> result

(**
(**
Perform query and return results via callback for each row
@raise Oops on error
*)
Expand All @@ -61,7 +61,7 @@ module type M = sig
*)
val select1 : connection -> string -> (statement -> result) -> (row -> 'b) -> 'b option

(** Execute non-query.
(** Execute non-query.
@raise Oops on error
@return number of affected rows
*)
Expand Down
5 changes: 2 additions & 3 deletions lib/parser.ml
@@ -1,6 +1,6 @@

module T_SQL_parser =
struct
module T_SQL_parser =
struct
type token = Sql_parser.token
type result = RA.Schema.t * Stmt.params * Stmt.kind
let rule = Sql_lexer.parse_rule
Expand All @@ -10,4 +10,3 @@ module T_SQL_parser =
module T = Parser_utils.Make (T_SQL_parser)

let parse_stmt stmt = T.parse_buf_exn (Lexing.from_string stmt)

10 changes: 5 additions & 5 deletions lib/rA.ml
Expand Up @@ -64,7 +64,7 @@ struct

let natural t1 t2 =
try natural_ t1 t2 with
| _ -> raise (Error (t1,"no common attributes for natural join of " ^
| _ -> raise (Error (t1,"no common attributes for natural join of " ^
(names t1) ^ " and " ^ (names t2)))

let join_using l t1 t2 =
Expand All @@ -78,12 +78,12 @@ struct
| Type.Any, _
| _, Type.Any -> ()
| x, y when x = y -> ()
| _ -> raise (Error (t1, sprintf "Atributes do not match : %s of type %s and %s of type %s"
| _ -> raise (Error (t1, sprintf "Atributes do not match : %s of type %s and %s of type %s"
a1.name (Type.to_string a1.domain)
a2.name (Type.to_string a2.domain)))) t1 t2

let check_types t1 t2 =
try check_types t1 t2 with
let check_types t1 t2 =
try check_types t1 t2 with
| List.Different_list_size _ -> raise (Error (t1, (to_string t1) ^ " differs in size to " ^ (to_string t2)))

let compound t1 t2 = check_types t1 t2; t1
Expand All @@ -95,7 +95,7 @@ struct
match pos with
| `First -> col::t
| `Default -> t @ [col]
| `After name ->
| `After name ->
try
let (i,_) = List.findi (fun _ attr -> by_name name attr) t in
let (l1,l2) = List.split_nth (i+1) t in
Expand Down
4 changes: 2 additions & 2 deletions lib/sql_parser.mly
Expand Up @@ -116,7 +116,7 @@ statement: CREATE ioption(temporary) TABLE ioption(if_not_exists) name=IDENT sch
Tables.add (name,s);
([],p,Create name)
}
| CREATE UNIQUE? INDEX if_not_exists? name=table_name
| CREATE UNIQUE? INDEX if_not_exists? name=table_name
ON table=table_name cols=sequence(index_column)
{
RA.Schema.project cols (Tables.get_schema table) |> ignore; (* just check *)
Expand Down Expand Up @@ -191,7 +191,7 @@ table_definition: t=sequence_(column_def1) table_def_done { List.filter_map (fun
table_def_done: table_def_done1 RPAREN IGNORED* { Parser_state.mode_normal () }
table_def_done1: { Parser_state.mode_ignore () }

select_stmt_t: select_core other=list(preceded(compound_op,select_core))
select_stmt_t: select_core other=list(preceded(compound_op,select_core))
o=loption(order) lim=limit_t?
{
let (s1,p1,tbls,cardinality) = $1 in
Expand Down
3 changes: 1 addition & 2 deletions lib/stmt.ml
Expand Up @@ -9,7 +9,7 @@ let params_to_string ps = Show.show<params>(ps)

type insert_kind = Values | Assign deriving(Show)

(** inferred inserted values to complete sql statement *)
(** inferred inserted values to complete sql statement *)
type inferred = (insert_kind * RA.Schema.t) option deriving(Show)

type cardinality = [`Zero_one | `One | `Nat] deriving(Show)
Expand All @@ -28,4 +28,3 @@ type kind = | Select of cardinality (** possible number of rows *)
deriving (Show)

type t = { schema : RA.Schema.t; params : params; kind : kind; props : Props.t; }

7 changes: 3 additions & 4 deletions lib/syntax.ml
Expand Up @@ -99,7 +99,7 @@ let infer_schema columns tables joined_schema =
let test_all_grouping columns =
let test = function
(* grouping function of zero or single parameter *)
| Expr (`Func ((_,true),args),_) when List.length args <= 1 -> true
| Expr (`Func ((_,true),args),_) when List.length args <= 1 -> true
| _ -> false
in
List.for_all test columns
Expand Down Expand Up @@ -177,10 +177,10 @@ let all_tbl_columns = all_columns $ List.map snd
let split_column_assignments tables l =
let cols = ref [] in
let exprs = ref [] in
let all = all_tbl_columns tables in
let all = all_tbl_columns tables in
List.iter (fun ((cname,tname as col),expr) ->
cols := col :: !cols;
let schema =
let schema =
match tname with
| Some name -> Tables.get_from tables name |> snd
| None -> all
Expand All @@ -202,4 +202,3 @@ let rec ensure_simple_expr = function
| `Column _ -> failwith "Not a simple expression"
| `Func ((_,grouping),_) when grouping -> failwith "Grouping function not allowed in simple expression"
| `Func (x,l) -> `Func(x,List.map ensure_simple_expr l)

4 changes: 2 additions & 2 deletions sql/real.sql
@@ -1,12 +1,12 @@
create table codeTable (locat INT, code TEXT, descript TEXT);

select *
select *
from codeTable
where locat not in (@lim1, @lim2)
and code not in
(
select code
from
from
(select code, descript // gets unique code-and-descript combos
from codeTable
where locat not in (@lim1, @lim2)
Expand Down
2 changes: 1 addition & 1 deletion sql/sample-hsqldb.sql
Expand Up @@ -40,7 +40,7 @@ create table PRODUCT (
CONSTRAINT FK_M2M FOREIGN KEY (MANUFACTURER_ID) REFERENCES MANUFACTURER (MANUFACTURER_ID)
);

-- test junction table
-- test junction table
create table DELIVERY (
CUSTOMER_ID INTEGER,
PRODUCT_ID INTEGER,
Expand Down
2 changes: 1 addition & 1 deletion sql/some.sql
@@ -1,7 +1,7 @@
create table [OrderLine] (Id int, OrderId int, ProductId int, Qty int, Status int);
create table [Product] (Id int, Name text, Price float);

select OrderId, count(*)
select OrderId, count(*)
from OrderLine
group by OrderId
having count(*) > @cnt;
Expand Down
76 changes: 38 additions & 38 deletions sql/stress.sql
@@ -1,67 +1,67 @@
SELECT xx.xx_rec_id promise_unit_ID,
xx.xx_volume aggregate_volume,
xx_category category,
xx_difference difference,
xx_initial_liability_amt initial_liability,
xx_out_of_pocket out_of_pocket,
SELECT xx.xx_rec_id promise_unit_ID,
xx.xx_volume aggregate_volume,
xx_category category,
xx_difference difference,
xx_initial_liability_amt initial_liability,
xx_out_of_pocket out_of_pocket,
xx_holdings_Secured_Flag holdings_UNSECURED_FLAG,
xx.xx_normal_liability_chart normal_liability_chart,
xx.xx_facility_liability_chart FACILITY_liability_chart,
yy.yy_rec_i target_REC_ID,
xx.xx_facility_liability_chart FACILITY_liability_chart,
yy.yy_rec_i target_REC_ID,
yy.yy_prediction_meter chart_prediction_meter,
yy.yy_unique_instance_liability_chart unique_instance_liability_chart,
yy.yy_target_liability_chart target_liability_chart,
xx.xx_indicator_id,
xx.xx_unused_src_calc UNUSED_count_SOURCE,
yy.yy_target_nm target_identifier,
yy.yy_target_id target_ID,
yy.yy_target_liability_chart target_liability_chart,
xx.xx_indicator_id,
xx.xx_unused_src_calc UNUSED_count_SOURCE,
yy.yy_target_nm target_identifier,
yy.yy_target_id target_ID,
xx.xx_facility_id mqxy_promise_unit_ID,
xx.xx_amt mqxy_unit_present_count,
xx.xx_units mqxy_unit_present_units,
xx.xx_standard_amt mqxy_standard_promise_count,
xx.xx_amt mqxy_unit_present_count,
xx.xx_units mqxy_unit_present_units,
xx.xx_standard_amt mqxy_standard_promise_count,
xx.xx_units mqxy_standard_unit_units,
to_CHAR(trunc(xx_during_contract_DT)) during_contract_DATE,
to_CHAR(trunc(xx_termination_DT)) termination_DATE,
to_CHAR(trunc(xx.xx_expiration_DT)) expiration_DATE,
nvl(agreement_aggregate.agreement_aggregate,0) agreement_aggregate,
nvl(lc_aggregate.lc_aggregate,0) LC_aggregate,
r.r_xoynx_RTG xoynxS_RATING,
r.r_grrrr_RTG grrrr_RATING
FROM (SELECT yy.xx_rec_id,
SUM(yy.l_count) agreement_aggregate
FROM target yy,
promise_agreement zz,
promise_unit aa,
agreement_unit lo
nvl(lc_aggregate.lc_aggregate,0) LC_aggregate,
r.r_xoynx_RTG xoynxS_RATING,
r.r_grrrr_RTG grrrr_RATING
FROM (SELECT yy.xx_rec_id,
SUM(yy.l_count) agreement_aggregate
FROM target yy,
promise_agreement zz,
promise_unit aa,
agreement_unit lo
WHERE zz.yy_rec_id = yy.yy_rec_id AND
xx.ca_rec_id = zz.ca_rec_id AND
lo.xx_rec_id = xx.xx_rec_id
lo.xx_rec_id = xx.xx_rec_id
GROUP BY yy.yy_rec_id,
lo.xx_rec_id
) agreement_aggregate,
(SELECT lc.xx_rec_id,
) agreement_aggregate,
(SELECT lc.xx_rec_id,
SUM(lc.lc_amt) lc_aggregate
FROM target yy,
promise_agreement zz,
promise_unit aa,
FROM target yy,
promise_agreement zz,
promise_unit aa,
lc_unit lc
WHERE zz.yy_rec_id = yy.yy_rec_id AND
xx.ca_rec_id = zz.ca_rec_id AND
lc.xx_rec_id = xx.xx_rec_id
GROUP BY yy.yy_rec_id,
GROUP BY yy.yy_rec_id,
lc.xx_rec_id
) lc_aggregate,
target yy,
promise_agreement zz,
rating r,
promise_unit cs
) lc_aggregate,
target yy,
promise_agreement zz,
rating r,
promise_unit cs
WHERE zz.yy_rec_id = yy.yy_rec_id AND
r.yy_rec_id = yy.yy_rec_id AND
xx.ca_rec_id = zz.ca_rec_id AND
lc_aggregate.xx_rec_id = xx.xx_rec_id AND
agreement_aggegate.xx_rec_id = xx.xx_rec_id AND
xx.xx_indicator_id = 1 AND
zz.ca_indicator_id = 1 AND
( r.r_indicator_id = 1 OR
( r.r_indicator_id = 1 OR
r.r_indicator_id IS NULL)
ORDER BY target_identifier
9 changes: 4 additions & 5 deletions src/cli.ml
Expand Up @@ -9,7 +9,7 @@ module Xml_gen = Gen.Make(Gen_xml)
module Java = Gen.Make(Gen_java)
module CSharp = Gen.Make(Gen_csharp)

(*
(*
common usecase:
sqlgg [-gen none] ddl.sql -gen cxx dml.sql
*)
Expand Down Expand Up @@ -48,7 +48,7 @@ let each_input =
| "-" -> run (Some stdin)
| filename -> Main.with_channel filename run

let generate l =
let generate l =
match !generate with
| None -> ()
| Some f -> f !name (List.enum l)
Expand Down Expand Up @@ -81,17 +81,16 @@ let main () =
Arg.parse args work usage_msg;
match !l with
| [] -> if Array.length Sys.argv = 1 then Arg.usage args usage_msg; 0
| l ->
| l ->
if !Error.errors then
begin Error.log "Errors encountered, no code generated"; 1 end
else
begin generate @@ List.concat @@ List.rev l; 0 end

let main () =
let main () =
try
main ()
with
exn -> Error.logs (Printexc.to_string exn); 2

let () = exit (main ())

2 changes: 1 addition & 1 deletion src/error.ml
Expand Up @@ -9,6 +9,6 @@ let log format = ksprintf logs format
(* let report format = ksprintf (fun str -> logs ("Project : warning _____: " ^ str)) format *)
(* let report = log *)

(* VS error format:
(* VS error format:
path(lineno) : warning _____: string
*)
7 changes: 3 additions & 4 deletions src/gen.ml
Expand Up @@ -83,15 +83,15 @@ let get_sql stmt =
match !params_mode with
| None -> sql
| Some subst ->
let f = match subst with
let f = match subst with
| Named -> subst_named
| Unnamed -> subst_unnamed
| Oracle -> subst_oracle
| Oracle -> subst_oracle
| PostgreSQL -> subst_postgresql
in
substitute_params sql stmt.params f

let time_string () =
let time_string () =
let module U = Unix in
let t = U.time () |> U.gmtime in
sprintf "%04u-%02u-%02uT%02u:%02uZ" (1900 + t.U.tm_year) (t.U.tm_mon+1) t.U.tm_mday t.U.tm_hour t.U.tm_min
Expand Down Expand Up @@ -136,4 +136,3 @@ let process name stmts =
S.generate out name stmts

end

0 comments on commit dafd55e

Please sign in to comment.