diff options
author | Sébastien Dailly <sebastien@dailly.me> | 2024-12-11 22:04:40 +0100 |
---|---|---|
committer | Sébastien Dailly <sebastien@dailly.me> | 2024-12-12 14:19:48 +0100 |
commit | 39f39919fb4749787393e95503f9814912265a73 (patch) | |
tree | 57745ab257e50f9ef4d6924c3c77d51fd8fb4d4d | |
parent | 5a558038874765f20b9dc1bcb1890600e2a2065d (diff) |
Review the consistency request
-rw-r--r-- | bin/importer.ml | 103 | ||||
-rw-r--r-- | lib/analysers/dependency.ml | 8 | ||||
-rw-r--r-- | lib/analysers/query.ml | 155 | ||||
-rw-r--r-- | lib/analysers/query.mli | 7 | ||||
-rw-r--r-- | lib/configuration/importConf.ml | 8 | ||||
-rw-r--r-- | lib/configuration/importConf.mli | 4 | ||||
-rw-r--r-- | lib/configuration/of_json.ml | 5 | ||||
-rw-r--r-- | lib/configuration/read_conf.ml | 2 | ||||
-rw-r--r-- | lib/configuration/syntax.ml | 69 | ||||
-rw-r--r-- | lib/data_types/table.ml | 9 | ||||
-rw-r--r-- | lib/sql/db.ml | 4 | ||||
-rw-r--r-- | lib/sql/db.mli | 41 | ||||
-rw-r--r-- | tests/analyser_query_test.ml | 20 | ||||
-rw-r--r-- | tests/confLoader.ml | 8 | ||||
-rw-r--r-- | tests/configuration_toml.ml | 28 |
15 files changed, 256 insertions, 215 deletions
diff --git a/bin/importer.ml b/bin/importer.ml index 0d9b751..4ca04fd 100644 --- a/bin/importer.ml +++ b/bin/importer.ml @@ -101,12 +101,11 @@ module Args = struct } end -(** Print the result from the query. +(** Print the result from the query. - Each value is given with the associated expression in the configuration, - the function is expected to convert the result into string in order to - include the content in the output CSV. - *) + Each value is given with the associated expression in the configuration, the + function is expected to convert the result into string in order to include + the content in the output CSV. *) let printer : Path.t ImportExpression.T.t * ImportCSV.DataType.t -> string = fun (column, value) -> ignore column; @@ -169,50 +168,52 @@ let process_table : let text_headers = Array.map v ~f:ImportCSV.DataType.to_string in Headers.SheeetMap.add source text_headers map in + headers - (* For each external check if the values are loaded *) - let dependancies = - ImportConf.get_dependancies_for_table conf.configuration source - in - List.iter dependancies ~f:(fun ext -> - match ext.ImportConf.Syntax.allow_missing with - | true -> () - | false -> ( - Printf.printf "Checking dependancies for %s %!" - ext.ImportConf.Syntax.target.ImportDataTypes.Table.name; - try - ignore - @@ Db.check_foreign db conf.configuration ext ~f:(fun values -> - Helpers.Console.update_cursor (); - - let row = - match snd (Array.get values 0) with - | ImportCSV.DataType.Integer i -> i - | _ -> -1 - and value = snd (Array.get values 1) in - let error = - ImportErrors. - { - source; - sheet = source.Table.tab; - row; - value; - target = Some ext.ImportConf.Syntax.target; - exn = - Failure - (Printf.sprintf "Key '%s' not found" - (CSV.DataType.to_string value)); - } - in - - ImportErrors.output_error log_error error); - Helpers.Console.close_cursor () - with - | Sqlite3.Error _ -> - (* We can have errors here if we have cycles in the +let check_deps : + 'a Db.t -> Csv.out_channel Lazy.t -> ImportConf.Syntax.t -> Table.t -> unit + = + fun db log_error conf source -> + (* For each external check if the values are loaded *) + let dependancies = ImportConf.get_dependancies_for_table conf source in + List.iter dependancies ~f:(fun ext -> + match ext.ImportConf.Syntax.Extern.allow_missing with + | true -> () + | false -> ( + Printf.printf "Checking dependancies for %s\n%!" + ext.ImportConf.Syntax.Extern.target.ImportDataTypes.Table.name; + try + ignore + @@ Db.check_foreign db conf ext ~f:(fun values -> + Helpers.Console.update_cursor (); + + let row = + match snd (Array.get values 0) with + | ImportCSV.DataType.Integer i -> i + | _ -> -1 + and value = snd (Array.get values 1) in + let error = + ImportErrors. + { + source; + sheet = source.Table.tab; + row; + value; + target = Some ext.ImportConf.Syntax.Extern.target; + exn = + Failure + (Printf.sprintf "Key '%s' not found" + (CSV.DataType.to_string value)); + } + in + + ImportErrors.output_error log_error error); + Helpers.Console.close_cursor () + with + | Sqlite3.Error _ -> + (* We can have errors here if we have cycles in the dependencies, but it’s OK at this step.*) - ())); - headers + ())) let () = let conf = Args.load () in @@ -283,6 +284,10 @@ let () = List.fold_left process_order ~init:Headers.SheeetMap.empty ~f:(process_table db dirname log_error conf) in + let () = + check_deps db log_error conf.configuration + conf.configuration.source + in let first_line = Headers.columns conf.configuration headers in Csv.output_record out_csv first_line; @@ -291,13 +296,11 @@ let () = ignore @@ Db.create_view db conf.configuration; Printf.printf "Extracting results %!"; match - Db.query - ~f:(fun v -> + Db.query db conf.configuration ~f:(fun v -> let arr = Array.to_seq v |> Seq.map printer |> List.of_seq in Helpers.Console.update_cursor (); Csv.output_record out_csv arr) - db conf.configuration with | Ok () -> Helpers.Console.close_cursor (); diff --git a/lib/analysers/dependency.ml b/lib/analysers/dependency.ml index e81cc49..9dd4736 100644 --- a/lib/analysers/dependency.ml +++ b/lib/analysers/dependency.ml @@ -52,7 +52,7 @@ type 'a expression_extractor = { } (** [add_path_in_map f parent path ] Extract the column from element [path] and - process the column in the function [f] + process the column in the function [f] The [path] is abstract, but the function [f.of_path] can extract the needed elements in order to add it in the mapping. @@ -107,8 +107,8 @@ let add_columns_in_map : expression and extracting the path contained inside. This function is called for each path declared inside the expression. *) -let add_dependancies : conf:Syntax.t -> Syntax.extern -> deps -> Path.t -> deps - = +let add_dependancies : + conf:Syntax.t -> Syntax.Extern.t -> deps -> Path.t -> deps = fun ~conf extern graph path -> let source_table = ImportConf.get_table_for_name conf path.Path.alias in @@ -120,7 +120,7 @@ let add_dependancies : conf:Syntax.t -> Syntax.extern -> deps -> Path.t -> deps | _ -> (target, [ source ]) :: graph let add_external_in_map : - conf:Syntax.t -> Syntax.extern -> build_map * deps -> build_map * deps = + conf:Syntax.t -> Syntax.Extern.t -> build_map * deps -> build_map * deps = fun ~conf extern (map, graph) -> let dest = ImportContainers.KeyName.from_table extern.target in (* Pre-check that every source is already declared in the configuration. *) diff --git a/lib/analysers/query.ml b/lib/analysers/query.ml index 7a6dd2a..dff3b9d 100644 --- a/lib/analysers/query.ml +++ b/lib/analysers/query.ml @@ -96,14 +96,14 @@ let show_path : conf:Syntax.t -> Format.formatter -> Path.t -> unit = let table_name = table.Table.name in Format.fprintf buffer "'%s'.col_%d" table_name column -(** Extract the informations from the dependancies. We get two informations here : +(** Extract the informations from the dependancies. We get two informations here + : - - the join query in order to load the data from the external column - - the column corresponding to the key in order to identify the missing - links later. - *) + - the join query in order to load the data from the external column + - the column corresponding to the key in order to identify the missing links + later. *) let query_of_external : - conf:Syntax.t -> join_buffer:Chunk.t -> Syntax.extern -> unit = + conf:Syntax.t -> join_buffer:Chunk.t -> Syntax.Extern.t -> unit = fun ~conf ~join_buffer external_ -> let extern_table = Table.name external_.target in @@ -117,12 +117,12 @@ let query_of_external : in Chunk.add_parameters join_buffer (Queue.to_seq q))) - (print_column external_.Syntax.target - ("key_" ^ external_.Syntax.target.name)); + (print_column external_.Syntax.Extern.target + ("key_" ^ external_.Syntax.Extern.target.name)); Format.pp_print_flush formatter () -(** Create the from part of the query, adding all the reuired externals. +(** Create the from part of the query, adding all the reuired externals. SQLite is able to optimize the query and do not load the table not used in the select clause. *) @@ -139,7 +139,7 @@ let create_from_chunck : Syntax.t -> Chunk.t -> unit = (** Build a CTE query in order to use any group function inside the query. Return the binded parameters used in the expression. The buffer given in - argument is also modified during the construction. + argument is also modified during the construction. If filters is not None, the clauses are added to the CTE. *) let build_cte : @@ -181,10 +181,10 @@ type filter_evaluation = { parameters : ImportCSV.DataType.t Seq.t; cte : (string * Chunk.t) option; } -(** Build the filters to apply in the query. We make the difference here - between the predicates to apply directly in the query, and the filters - associated with a group, which are required to be transformed into a CTE -in SQL, and are evaluated before. *) +(** Build the filters to apply in the query. We make the difference here between + the predicates to apply directly in the query, and the filters associated + with a group, which are required to be transformed into a CTE in SQL, and + are evaluated before. *) (** Evaluate the filters on the query *) let eval_filters : Syntax.t -> filter_evaluation = @@ -274,7 +274,7 @@ type query = { } (** Build the query and return also the mapping in order to identify each - external links between files. + external links between files. The select query will name each column with an alias, and the map allow to find which source is pointed by this alias. *) @@ -371,61 +371,98 @@ let select : Syntax.t -> query * Path.t ImportExpression.T.t array = ({ q = Buffer.contents b; parameters = Queue.to_seq parameters }, headers) -let check_external : Syntax.t -> Syntax.extern -> query = +let check_external : Syntax.t -> Syntax.Extern.t -> query = fun conf external_ -> - let extern_table = Table.name external_.target in - - let parameters = Queue.create () in - let internal_key_buffer = Buffer.create 16 in - let formatter = Format.formatter_of_buffer internal_key_buffer in - let internal_key_seq = - Q.query_of_expression Q.BindParam formatter (show_path ~conf) - external_.intern_key + let internal_chunk = + let internal_key_buffer = Buffer.create 16 in + let formatter = Format.formatter_of_buffer internal_key_buffer in + let internal_key_seq = + Q.query_of_expression Q.BindParam formatter (show_path ~conf) + external_.Syntax.Extern.intern_key + in + Format.pp_print_flush formatter (); + Chunk.create' internal_key_buffer (Queue.copy internal_key_seq) in - Format.pp_print_flush formatter (); let external_key_buffer = Buffer.create 16 in - let pointed_tables = pointed_tables conf external_.intern_key in Buffer.add_string external_key_buffer - (print_column external_.Syntax.target - ("key_" ^ external_.Syntax.target.name)); + (print_column external_.Syntax.Extern.target + ("key_" ^ external_.Syntax.Extern.target.name)); + let pointed_tables = pointed_tables conf external_.intern_key in + + let parameters = Queue.create () in (* We do a copy before the transfert because the Queue is reused later in the query *) - Queue.transfer (Queue.copy internal_key_seq) parameters; + Queue.transfer (Queue.copy internal_chunk.parameters) parameters; + + (* We have to link all the tables referenced by the external, we cannot let + any table not linked with the source in the request (this would cause a + cartesian product request) + + This not the usual way to proceed (we start from the source and link the externals) + *) + let rec collect_links : + Syntax.Extern.t -> Syntax.Extern.t list -> Syntax.Extern.t list = + fun table init -> + let res = + (* Do not add the same external if the value is already present *) + let init = + match List.find_opt init ~f:(fun ext -> table == ext) with + | None -> table :: init + | Some _ -> init + in + + Expression.T.fold_values ~init table.Syntax.Extern.intern_key + ~f:(fun acc expr -> + match expr.Path.alias with + | None -> acc + | Some _ as path -> ( + let table = ImportConf.get_table_for_name conf path in + (* Look for this table in the externals *) + let external_opt = + List.find_opt conf.Syntax.externals ~f:(fun t -> + t.Syntax.Extern.target == table) + in + match external_opt with + | None -> acc + | Some ext -> collect_links ext acc)) + in + res + in + let dependencies = collect_links external_ [] in let join_content = Buffer.contents external_key_buffer in - let inner_content = Buffer.contents internal_key_buffer in - let b = Buffer.create 256 in - let formatter = Format.formatter_of_buffer b in + let request = Chunk.create () in + Chunk.add_string request "SELECT "; let () = - Format.fprintf formatter - "SELECT %a%s FROM%a LEFT JOIN '%s' AS '%s' ON %t = %s WHERE %s IS NULL \ - AND %s IS NOT NULL AND %s <> ''" - (fun formatter -> function - | [ (table, _name) ] -> - Format.fprintf formatter "%s, " (print_column table "id") - | _ -> Format.fprintf formatter "-1, ") - pointed_tables (* *) - inner_content (* *) - (Format.pp_print_list - ~pp_sep:(fun f () -> Format.pp_print_text f ", ") - (fun formatter (table, name) -> - Format.fprintf formatter "\n'%s' AS '%s'" name table.Table.name)) - pointed_tables (* *) - extern_table (* *) - external_.target.name - (prepare_key ~f:(fun b -> - Format.pp_print_text b (Buffer.contents internal_key_buffer))) - join_content (* *) - join_content (* *) - inner_content (* *) - inner_content + match pointed_tables with + | [] -> + (* Otherwise, just return -1 *) + Chunk.add_string request "-1" + | (table, _name) :: _ -> + (* If we have a single source, extract the row number. *) + Chunk.add_string request (print_column table "id") in + Chunk.add_string request ", "; + Chunk.append ~head:request ~tail:(Chunk.copy internal_chunk); + Chunk.add_string request " FROM\n'"; + Chunk.add_string request (Table.name conf.source); + Chunk.add_string request "' AS '"; + Chunk.add_string request conf.source.name; + Chunk.add_string request "'"; - Format.pp_print_flush formatter (); - - { q = Buffer.contents b; parameters = Queue.to_seq parameters } + (* Add the externals in the query *) + List.iter dependencies ~f:(query_of_external ~conf ~join_buffer:request); + Chunk.add_string request " WHERE "; + Chunk.add_string request join_content; + Chunk.add_string request " IS NULL AND "; + Chunk.append ~head:request ~tail:(Chunk.copy internal_chunk); + Chunk.add_string request " IS NOT NULL AND "; + Chunk.append ~head:request ~tail:(Chunk.copy internal_chunk); + Chunk.add_string request " <> ''"; + let q = Buffer.contents request.b in + { q; parameters = Queue.to_seq request.parameters } let build_key_insert : Buffer.t -> Dependency.key -> unit = fun buffer { Dependency.expression; _ } -> @@ -440,6 +477,4 @@ let build_key_insert : Buffer.t -> Dependency.key -> unit = Q.query_of_expression Q.NoParam formatter show_column expression) in - Format.pp_print_flush formatter (); - - () + Format.pp_print_flush formatter () diff --git a/lib/analysers/query.mli b/lib/analysers/query.mli index 14d2807..520718a 100644 --- a/lib/analysers/query.mli +++ b/lib/analysers/query.mli @@ -6,14 +6,13 @@ type query = { q : string; (** The query to execute *) parameters : ImportCSV.DataType.t Seq.t; } -(** This type represent a query to execute. - [q] is the template to run, and shall be run with all the binded parameters. - *) +(** This type represent a query to execute. [q] is the template to run, and + shall be run with all the binded parameters. *) val select : Syntax.t -> query * ImportDataTypes.Path.t ImportExpression.T.t array -val check_external : Syntax.t -> Syntax.extern -> query +val check_external : Syntax.t -> Syntax.Extern.t -> query (** Create a query which select all the missing key in an external *) val build_key_insert : Buffer.t -> Dependency.key -> unit diff --git a/lib/configuration/importConf.ml b/lib/configuration/importConf.ml index 586be3c..eb7c8d2 100644 --- a/lib/configuration/importConf.ml +++ b/lib/configuration/importConf.ml @@ -60,18 +60,18 @@ let get_table_for_name : Syntax.t -> string option -> Table.t = if String.equal name conf.source.name then conf.source else let ext = - List.find conf.externals ~f:(fun (ext : Syntax.extern) -> + List.find conf.externals ~f:(fun (ext : Syntax.Extern.t) -> String.equal name ext.target.name) in ext.target let root_table : Syntax.t -> Table.t = fun conf -> conf.source -let get_dependancies_for_table : Syntax.t -> Table.t -> Syntax.extern list = +let get_dependancies_for_table : Syntax.t -> Table.t -> Syntax.Extern.t list = fun conf source -> let is_root = source = conf.source in - List.filter conf.externals ~f:(fun (ext : Syntax.extern) -> + List.filter conf.externals ~f:(fun (ext : Syntax.Extern.t) -> (* Enumerate the intern_key and check the source pointed by each column *) Expression.fold_values ext.intern_key ~init:false ~f:(fun acc expr -> if acc then acc @@ -83,7 +83,7 @@ let get_dependancies_for_table : Syntax.t -> Table.t -> Syntax.extern list = let print_path_expression t = ImportExpression.Repr.repr Path.repr t let print_extern t = - let toml = Syntax.toml_of_extern t in + let toml = Syntax.Extern.toml_of_extern t in Otoml.Printer.to_string toml let expression_from_string s = diff --git a/lib/configuration/importConf.mli b/lib/configuration/importConf.mli index 3a8ae75..be1d1d4 100644 --- a/lib/configuration/importConf.mli +++ b/lib/configuration/importConf.mli @@ -12,7 +12,7 @@ val t_of_yojson : Yojson.Safe.t -> Syntax.t val t_of_toml : Otoml.t -> (Syntax.t, string) result val get_table_for_name : Syntax.t -> string option -> Table.t -val get_dependancies_for_table : Syntax.t -> Table.t -> Syntax.extern list +val get_dependancies_for_table : Syntax.t -> Table.t -> Syntax.Extern.t list (** Get all the externals refered by the source *) val print_path_expression : Path.t ImportExpression.T.t -> string @@ -20,4 +20,4 @@ val print_path_expression : Path.t ImportExpression.T.t -> string val expression_from_string : string -> (Path.t ImportExpression.T.t, string) result -val print_extern : Syntax.extern -> string +val print_extern : Syntax.Extern.t -> string diff --git a/lib/configuration/of_json.ml b/lib/configuration/of_json.ml index f9171b9..e6ee7a4 100644 --- a/lib/configuration/of_json.ml +++ b/lib/configuration/of_json.ml @@ -2,7 +2,6 @@ open StdLabels module Table = ImportDataTypes.Table module Path = ImportDataTypes.Path module Expression = ImportExpression.T - open Ppx_yojson_conv_lib.Yojson_conv.Primitives let current_syntax = 1 @@ -100,7 +99,7 @@ type extern = { } [@@deriving of_yojson] -type syntax_v1_extern = Syntax.extern +type syntax_v1_extern = Syntax.Extern.t let syntax_v1_extern_of_yojson yojson = let e = extern_of_yojson yojson in @@ -108,7 +107,7 @@ let syntax_v1_extern_of_yojson yojson = Expression.map e.intern_key ~f:(fun column -> Syntax.Path.{ column; alias = e.source }) in - Syntax. + Syntax.Extern. { extern_key = e.extern_key; intern_key; diff --git a/lib/configuration/read_conf.ml b/lib/configuration/read_conf.ml index 8d467a5..952c43c 100644 --- a/lib/configuration/read_conf.ml +++ b/lib/configuration/read_conf.ml @@ -161,7 +161,7 @@ module Make (S : Decoders.Decode.S) = struct in S.succeed - Syntax. + Syntax.Extern. { intern_key; extern_key; diff --git a/lib/configuration/syntax.ml b/lib/configuration/syntax.ml index 8efdc59..1eb3c70 100644 --- a/lib/configuration/syntax.ml +++ b/lib/configuration/syntax.ml @@ -13,46 +13,49 @@ let toml_of_table Table.{ file; tab; name } = Otoml.table values -type extern = { - intern_key : Path.t E.t; - target : Table.t; - extern_key : Path.column E.t; - allow_missing : bool; - match_rule : string option; -} +module Extern = struct + type t = { + intern_key : Path.t E.t; + target : Table.t; + extern_key : Path.column E.t; + allow_missing : bool; + match_rule : string option; + } + (** Describe a relation beteween two tables *) -let toml_of_extern extern = - let values = - [ - ( "intern_key", - Otoml.string - @@ ImportExpression.Repr.repr ~top:true Path.repr extern.intern_key ); - ( "extern_key", - Otoml.string - @@ ImportExpression.Repr.repr ~top:true - (fun v -> ":" ^ ImportCSV.Csv.column_to_string v) - extern.extern_key ); - ("file", Otoml.string extern.target.file); - ("allow_missing", Otoml.boolean extern.allow_missing); - ] - in + let toml_of_extern extern = + let values = + [ + ( "intern_key", + Otoml.string + @@ ImportExpression.Repr.repr ~top:true Path.repr extern.intern_key ); + ( "extern_key", + Otoml.string + @@ ImportExpression.Repr.repr ~top:true + (fun v -> ":" ^ ImportCSV.Csv.column_to_string v) + extern.extern_key ); + ("file", Otoml.string extern.target.file); + ("allow_missing", Otoml.boolean extern.allow_missing); + ] + in - let values = - match extern.target.tab with - | 1 -> values - | tab -> ("tab", Otoml.integer tab) :: values - in + let values = + match extern.target.tab with + | 1 -> values + | tab -> ("tab", Otoml.integer tab) :: values + in - Otoml.table values + Otoml.table values -let toml_of_externs externs = - List.map externs ~f:(fun e -> (e.target.name, toml_of_extern e)) - |> Otoml.table + let toml externs = + List.map externs ~f:(fun e -> (e.target.name, toml_of_extern e)) + |> Otoml.table +end type t = { version : int; source : Table.t; - externals : extern list; + externals : Extern.t list; columns : Path.t E.t list; filters : Path.t E.t list; sort : Path.t E.t list; @@ -80,7 +83,7 @@ let repr t = [ ("version", Otoml.integer t.version); ("source", toml_of_table t.source); - ("externals", toml_of_externs t.externals); + ("externals", Extern.toml t.externals); ("sheet", sheet); ] in diff --git a/lib/data_types/table.ml b/lib/data_types/table.ml index d807c5c..82a7d95 100644 --- a/lib/data_types/table.ml +++ b/lib/data_types/table.ml @@ -6,9 +6,14 @@ type t = { name : string; } -(** Get the internal name for the given table. +(** Get the internal name for the given table. - This value may differ from the association name given in the configuration. *) + This value may differ from the association name given in the configuration. + This is because the same file can be linked more than one times. We need to + differenciate + + - the name of the table + - the name of how the table is used in a context *) let name : t -> string = fun source -> let file_name = diff --git a/lib/sql/db.ml b/lib/sql/db.ml index 89431b1..0f06f15 100644 --- a/lib/sql/db.ml +++ b/lib/sql/db.ml @@ -231,7 +231,7 @@ let insert : Error e (** This simple function convert a query generated by the application into a - statement executed with sqlite. + statement executed with sqlite. The function expect a perfect match between the query and the parameters. *) let execute_query : @@ -303,7 +303,7 @@ let check_foreign : f:((string * CSV.DataType.t) array -> unit) -> Sqlite3.db -> Syntax.t -> - Syntax.extern -> + Syntax.Extern.t -> unit T.result = fun ~f db conf external_ -> let query = ImportAnalyser.Query.check_external conf external_ in diff --git a/lib/sql/db.mli b/lib/sql/db.mli index 465b159..478d762 100644 --- a/lib/sql/db.mli +++ b/lib/sql/db.mli @@ -6,22 +6,21 @@ type 'a result = ('a, exn) Result.t val with_db : string -> ('a t -> unit result) -> unit result val check_table_schema : 'a t -> ImportAnalyser.Dependency.t -> bool result -(** Check if a table with the same structure already exists in the database. +(** Check if a table with the same structure already exists in the database. This query allow to reuse the same data without reloading the file if nothing changed. *) val create_table : 'a t -> ImportAnalyser.Dependency.t -> unit result -(** [create_table db name] will create a new table in the - db with the given name, and the columns from the configuration (see +(** [create_table db name] will create a new table in the db with the given + name, and the columns from the configuration (see [ImportAnalyser.Query.create_table]) Any previous table with the same name will be deleted. *) val prepare_insert : 'a t -> ImportAnalyser.Dependency.t -> Sqlite3.stmt result -(** Create a statement to use in an insert. - [prepare_insert db table] will prepare a statement for inserting - the columns at the given index. *) +(** Create a statement to use in an insert. [prepare_insert db table] will + prepare a statement for inserting the columns at the given index. *) val finalize : Sqlite3.stmt -> unit result (** Finalize the statement. The function shall be called once each insert are @@ -35,7 +34,7 @@ val eval_key : ImportAnalyser.Dependency.key list -> (int * ImportCSV.DataType.t) list -> (Sqlite3.stmt option * Sqlite3.Data.t list) result -(** Evaluate the keys in sqlite and get the results. +(** Evaluate the keys in sqlite and get the results. The function is intended to check if the values are null before inserting them in a batch *) @@ -46,17 +45,17 @@ val insert : id:int -> (int * ImportCSV.DataType.t) list -> unit result -(** Insert a new row in the database. +(** Insert a new row in the database. - [insert db ~id statement values] will add a new row in the given table with - [id]. The columns are identified with their index number (there is a - difference by one with the column number) + [insert db ~id statement values] will add a new row in the given table with + [id]. The columns are identified with their index number (there is a + difference by one with the column number) - Thanks to SQLite Flexible Typing (https://www.sqlite.org/flextypegood.html) - each column can contain values typed differently which is how the spreadsheet - also works. + Thanks to SQLite Flexible Typing (https://www.sqlite.org/flextypegood.html) + each column can contain values typed differently which is how the + spreadsheet also works. - This function is expected to be run inside a transaction. *) + This function is expected to be run inside a transaction. *) val begin_transaction : 'a t -> unit result val commit : 'a t -> unit result @@ -69,13 +68,11 @@ val query : 'a t -> Syntax.t -> unit result -(** This one the most important function from the application. The function - will transform the configuration into an sql query and will fetch the - result from the sqlite engine. +(** This one the most important function from the application. The function will + transform the configuration into an sql query and will fetch the result from + the sqlite engine. - The function [f] given in argument will be called for each line - - *) + The function [f] given in argument will be called for each line *) val create_view : 'a t -> Syntax.t -> unit result (** Create a view which represent the result *) @@ -84,7 +81,7 @@ val check_foreign : f:((string * ImportCSV.DataType.t) array -> unit) -> 'a t -> Syntax.t -> - Syntax.extern -> + Syntax.Extern.t -> unit result val clear_duplicates : diff --git a/tests/analyser_query_test.ml b/tests/analyser_query_test.ml index 3559de4..8f531ce 100644 --- a/tests/analyser_query_test.ml +++ b/tests/analyser_query_test.ml @@ -85,10 +85,10 @@ let check_externals = let expected_query = "SELECT 'source'.'id', 'source'.col_1 FROM\n\ - 'source' AS 'source' LEFT JOIN 'other' AS 'other' ON \ - rtrim(upper('source'.col_1)) = 'other'.'key_other' WHERE \ - 'other'.'key_other' IS NULL AND 'source'.col_1 IS NOT NULL AND \ - 'source'.col_1 <> ''" + 'source' AS 'source'\n\ + LEFT JOIN 'other' AS 'other' ON rtrim(upper('source'.col_1)) = \ + 'other'.'key_other' WHERE 'other'.'key_other' IS NULL AND 'source'.col_1 \ + IS NOT NULL AND 'source'.col_1 <> ''" in assert_equal ~printer:Fun.id expected_query query.q @@ -222,10 +222,10 @@ let prepare_insert = assert_equal ~printer:Fun.id expected contents -(** Test a request with a group in a filter. +(** Test a request with a group in a filter. -This generate a CTE expression in order to evaluate the group before loading -the results from the query. *) + This generate a CTE expression in order to evaluate the group before loading + the results from the query. *) let filter_group = "Test filter_group" >:: fun _ -> let c col = Expr.path ImportDataTypes.Path.{ alias = None; column = col } in @@ -253,10 +253,10 @@ WHERE (cte.group0)|} assert_equal ~printer:(fun s -> Printf.sprintf "\n%s" s) expected contents.q -(** Test a request with a group in a filter. +(** Test a request with a group in a filter. -This generate a CTE expression in order to evaluate the group before loading -the results from the query. *) + This generate a CTE expression in order to evaluate the group before loading + the results from the query. *) let filter_group2 = "Test filter_group" >:: fun _ -> let c col = Expr.path ImportDataTypes.Path.{ alias = None; column = col } in diff --git a/tests/confLoader.ml b/tests/confLoader.ml index 266ff33..bce4db0 100644 --- a/tests/confLoader.ml +++ b/tests/confLoader.ml @@ -39,7 +39,7 @@ let external_table_other = ImportDataTypes.Table.{ file = "other.xlsx"; tab = 1; name = "other" } let external_other = - ImportConf.Syntax. + ImportConf.Syntax.Extern. { intern_key = Path { alias = None; column = 1 }; target = external_table_other; @@ -52,7 +52,7 @@ let external_table_last = ImportDataTypes.Table.{ file = "last.xlsx"; tab = 1; name = "last_file" } let external_last = - ImportConf.Syntax. + ImportConf.Syntax.Extern. { intern_key = Path { alias = Some "other"; column = 1 }; target = external_table_last; @@ -124,5 +124,5 @@ let keys_printer : ImportAnalyser.Dependency.key list -> string = * Represents externals *) -let pp_externals : ImportConf.Syntax.extern list -> string = - fun ext -> ImportConf.Syntax.toml_of_externs ext |> Otoml.Printer.to_string +let pp_externals : ImportConf.Syntax.Extern.t list -> string = + fun ext -> ImportConf.Syntax.Extern.toml ext |> Otoml.Printer.to_string diff --git a/tests/configuration_toml.ml b/tests/configuration_toml.ml index 3c8bfc2..e58ff1b 100644 --- a/tests/configuration_toml.ml +++ b/tests/configuration_toml.ml @@ -10,21 +10,21 @@ let test_suit = match toml with | Error s -> raise (Failure s) | Ok result -> - let open ImportConf.Syntax in let expected = - { - target = { file = ""; tab = 1; name = "target" }; - extern_key = Literal "_B"; - intern_key = - Function - ( "function", - [ - Path { alias = None; column = 1 }; - Path { alias = None; column = 2 }; - ] ); - match_rule = None; - allow_missing = true; - } + ImportConf.Syntax.Extern. + { + target = { file = ""; tab = 1; name = "target" }; + extern_key = Literal "_B"; + intern_key = + Function + ( "function", + [ + Path { alias = None; column = 1 }; + Path { alias = None; column = 2 }; + ] ); + match_rule = None; + allow_missing = true; + } in let printer s = |