From 9c57974854de47bad24a2c9af9fc36155295137e Mon Sep 17 00:00:00 2001 From: Guillaume Petiot Date: Thu, 7 Nov 2024 15:16:01 +0000 Subject: [PATCH 1/4] Split odoc_driver into 3 sub-commands --- src/driver/common_args.ml | 114 ++++++++++++++++++++++++++ src/driver/odoc_driver.ml | 164 ++++++++++++++++---------------------- 2 files changed, 182 insertions(+), 96 deletions(-) create mode 100644 src/driver/common_args.ml diff --git a/src/driver/common_args.ml b/src/driver/common_args.ml new file mode 100644 index 0000000000..9cdd441bf5 --- /dev/null +++ b/src/driver/common_args.ml @@ -0,0 +1,114 @@ +open Cmdliner + +let fpath_arg = + let print ppf v = Fpath.pp ppf v in + Arg.conv (Fpath.of_string, print) + +let odoc_dir = + let doc = "Directory in which the intermediate odoc files go" in + Arg.(value & opt fpath_arg (Fpath.v "_odoc/") & info [ "odoc-dir" ] ~doc) + +let odocl_dir = + let doc = "Directory in which the intermediate odocl files go" in + Arg.(value & opt (some fpath_arg) None & info [ "odocl-dir" ] ~doc) + +let index_dir = + let doc = "Directory in which the index files go" in + Arg.(value & opt fpath_arg (Fpath.v "_indexes/") & info [ "index-dir" ] ~doc) + +let mld_dir = + let doc = "Directory in which the auto-generated mld files go" in + Arg.(value & opt fpath_arg (Fpath.v "_mlds/") & info [ "mld-dir" ] ~doc) + +let html_dir = + let doc = "Directory in which the generated HTML files go" in + Arg.(value & opt fpath_arg (Fpath.v "_html/") & info [ "html-dir" ] ~doc) + +let packages = + (* TODO: Is it package or library? *) + let doc = "The packages to document" in + Arg.(value & opt_all string [] & info [ "p" ] ~doc) + +let verbose = + let doc = "Enable verbose output" in + Arg.(value & flag & info [ "v"; "verbose" ] ~doc) + +let stats = + let doc = "Produce 'driver-benchmarks.json' with run stats" in + Arg.(value & flag & info [ "stats" ] ~doc) + +let nb_workers = + let doc = "Number of workers." in + Arg.(value & opt int 15 & info [ "j" ] ~doc) + +let odoc_bin = + let doc = "Odoc binary to use" in + Arg.(value & opt (some string) None & info [ "odoc" ] ~doc) + +let blessed = + let doc = "Blessed" in + Arg.(value & flag & info [ "blessed" ] ~doc) + +let compile_grep = + let doc = "Show compile commands containing the string" in + Arg.(value & opt (some string) None & info [ "compile-grep" ] ~doc) + +let link_grep = + let doc = "Show link commands containing the string" in + Arg.(value & opt (some string) None & info [ "link-grep" ] ~doc) + +let generate_grep = + let doc = "Show html-generate commands containing the string" in + Arg.(value & opt (some string) None & info [ "html-grep" ] ~doc) + +type t = { + packages : string list; + verbose : bool; + odoc_dir : Fpath.t; + odocl_dir : Fpath.t option; + index_dir : Fpath.t; + mld_dir : Fpath.t; + html_dir : Fpath.t; + stats : bool; + nb_workers : int; + odoc_bin : string option; + blessed : bool; + compile_grep : string option; + link_grep : string option; + generate_grep : string option; +} + +let term = + let open Term in + let ( let+ ) t f = const f $ t in + let ( and+ ) a b = const (fun x y -> (x, y)) $ a $ b in + let+ packages = packages + and+ verbose = verbose + and+ odoc_dir = odoc_dir + and+ odocl_dir = odocl_dir + and+ index_dir = index_dir + and+ mld_dir = mld_dir + and+ html_dir = html_dir + and+ stats = stats + and+ nb_workers = nb_workers + and+ odoc_bin = odoc_bin + and+ blessed = blessed + and+ compile_grep = compile_grep + and+ link_grep = link_grep + and+ generate_grep = generate_grep in + { + packages; + verbose; + odoc_dir; + odocl_dir; + index_dir; + mld_dir; + html_dir; + stats; + nb_workers; + odoc_bin; + blessed; + compile_grep; + link_grep; + generate_grep; + } diff --git a/src/driver/odoc_driver.ml b/src/driver/odoc_driver.ml index 61db7b6a91..1809659d88 100644 --- a/src/driver/odoc_driver.ml +++ b/src/driver/odoc_driver.ml @@ -551,9 +551,28 @@ let remap_virtual_interfaces duplicate_hashes pkgs = }) pkgs -let run libs verbose packages_dir odoc_dir odocl_dir index_dir mld_dir html_dir - stats nb_workers odoc_bin voodoo package_name blessed dune_style - compile_grep link_grep generate_grep = +type mode = + | Voodoo of { package_name : string } + | Dune of { path : Fpath.t } + | Opam of { packages_dir : Fpath.t option } + +let run mode + { + Common_args.packages; + verbose; + odoc_dir; + odocl_dir; + index_dir; + mld_dir; + html_dir; + stats; + nb_workers; + odoc_bin; + blessed; + compile_grep; + link_grep; + generate_grep; + } = Option.iter (fun odoc_bin -> Odoc.odoc := Bos.Cmd.v odoc_bin) odoc_bin; let _ = Voodoo.find_universe_and_version "foo" in Eio_main.run @@ fun env -> @@ -564,26 +583,19 @@ let run libs verbose packages_dir odoc_dir odocl_dir index_dir mld_dir html_dir let () = Worker_pool.start_workers env sw nb_workers in let all, extra_libs_paths = - match (voodoo, package_name, dune_style, packages_dir) with - | true, Some p, None, None -> + match mode with + | Voodoo { package_name = p } -> let all = Voodoo.of_voodoo p ~blessed in let extra_libs_paths = Voodoo.extra_libs_paths odoc_dir in (all, extra_libs_paths) - | false, None, Some dir, None -> - (Dune_style.of_dune_build dir, Util.StringMap.empty) - | false, None, None, packages_dir -> - let libs = if libs = [] then Ocamlfind.all () else libs in + | Dune { path } -> (Dune_style.of_dune_build path, Util.StringMap.empty) + | Opam { packages_dir } -> + let libs = if packages = [] then Ocamlfind.all () else packages in let libs = List.map Ocamlfind.sub_libraries libs |> List.fold_left Util.StringSet.union Util.StringSet.empty in (Packages.of_libs ~packages_dir libs, Util.StringMap.empty) - | true, None, _, _ -> failwith "--voodoo requires --package" - | false, Some _, _, _ -> failwith "--package requires --voodoo" - | true, _, _, Some _ | false, _, Some _, Some _ -> - failwith "--packages-dir is only useful in opam mode" - | true, _, Some _, _ -> - failwith "--voodoo and --dune-style are mutually exclusive" in let virtual_check = @@ -611,13 +623,14 @@ let run libs verbose packages_dir odoc_dir odocl_dir index_dir mld_dir html_dir let all = remap_virtual_interfaces virtual_check all in let partial = - if voodoo then - match Util.StringMap.to_list all with - | [ (_, p) ] -> - let output_path = Fpath.(odoc_dir // p.pkg_dir) in - Some output_path - | _ -> failwith "Error, expecting singleton library in voodoo mode" - else None + match mode with + | Voodoo _ -> ( + match Util.StringMap.to_list all with + | [ (_, p) ] -> + let output_path = Fpath.(odoc_dir // p.pkg_dir) in + Some output_path + | _ -> failwith "Error, expecting singleton library in voodoo mode") + | _ -> None in let () = Eio.Fiber.both @@ -661,92 +674,51 @@ let run libs verbose packages_dir odoc_dir odocl_dir index_dir mld_dir html_dir Format.eprintf "Total time: %f@.%!" (Stats.total_time ()); if stats then Stats.bench_results html_dir -let fpath_arg = - let print ppf v = Fpath.pp ppf v in - Arg.conv (Fpath.of_string, print) +module Voodoo_mode = struct + let run package_name = run (Voodoo { package_name }) -let odoc_dir = - let doc = "Directory in which the intermediate odoc files go" in - Arg.(value & opt fpath_arg (Fpath.v "_odoc/") & info [ "odoc-dir" ] ~doc) + let package_name = + let doc = "Name of package to process with voodoo" in + Arg.(value & pos 0 string "" & info [] ~doc) -let odocl_dir = - let doc = "Directory in which the intermediate odocl files go" in - Arg.(value & opt (some fpath_arg) None & info [ "odocl-dir" ] ~doc) + let cmd = + let doc = "Process output from voodoo-prep" in + let info = Cmd.info "voodoo" ~doc in + Cmd.v info Term.(const run $ package_name $ Common_args.term) +end -let index_dir = - let doc = "Directory in which the index files go" in - Arg.(value & opt fpath_arg (Fpath.v "_indexes/") & info [ "index-dir" ] ~doc) +module Dune_mode = struct + let run path = run (Dune { path }) -let mld_dir = - let doc = "Directory in which the auto-generated mld files go" in - Arg.(value & opt fpath_arg (Fpath.v "_mlds/") & info [ "mld-dir" ] ~doc) + let dune_style = + Arg.(value & pos 0 Common_args.fpath_arg (Fpath.v ".") & info []) -let html_dir = - let doc = "Directory in which the generated HTML files go" in - Arg.(value & opt fpath_arg (Fpath.v "_html/") & info [ "html-dir" ] ~doc) + let cmd = + let doc = "Dune mode" in + let info = Cmd.info "dune" ~doc in + Cmd.v info Term.(const run $ dune_style $ Common_args.term) +end -let packages = - (* TODO: Is it package or library? *) - let doc = "The packages to document" in - Arg.(value & opt_all string [] & info [ "p" ] ~doc) +module Opam_mode = struct + let run packages_dir = run (Opam { packages_dir }) -let verbose = - let doc = "Enable verbose output" in - Arg.(value & flag & info [ "v"; "verbose" ] ~doc) + let packages_dir = + let doc = "Packages directory under which packages should be output." in + Arg.( + value + & opt (some Common_args.fpath_arg) None + & info [ "packages-dir" ] ~doc) -let stats = - let doc = "Produce 'driver-benchmarks.json' with run stats" in - Arg.(value & flag & info [ "stats" ] ~doc) - -let nb_workers = - let doc = "Number of workers." in - Arg.(value & opt int 15 & info [ "j" ] ~doc) - -let odoc_bin = - let doc = "Odoc binary to use" in - Arg.(value & opt (some string) None & info [ "odoc" ] ~doc) - -let packages_dir = - let doc = "Packages directory under which packages should be output." in - Arg.(value & opt (some fpath_arg) None & info [ "packages-dir" ] ~doc) - -let voodoo = - let doc = "Process output from voodoo-prep" in - Arg.(value & flag & info [ "voodoo" ] ~doc) - -let package_name = - let doc = "Name of package to process with voodoo" in - Arg.(value & opt (some string) None & info [ "package" ] ~doc) - -let blessed = - let doc = "Blessed" in - Arg.(value & flag & info [ "blessed" ] ~doc) - -let dune_style = - let doc = "Dune style" in - Arg.(value & opt (some fpath_arg) None & info [ "dune-style" ] ~doc) - -let compile_grep = - let doc = "Show compile commands containing the string" in - Arg.(value & opt (some string) None & info [ "compile-grep" ] ~doc) - -let link_grep = - let doc = "Show link commands containing the string" in - Arg.(value & opt (some string) None & info [ "link-grep" ] ~doc) - -let generate_grep = - let doc = "Show html-generate commands containing the string" in - Arg.(value & opt (some string) None & info [ "html-grep" ] ~doc) + let cmd = + let doc = "Opam mode" in + let info = Cmd.info "opam" ~doc in + Cmd.v info Term.(const run $ packages_dir $ Common_args.term) +end let cmd = let doc = "Generate odoc documentation" in let info = Cmd.info "odoc_driver" ~doc in - Cmd.v info - Term.( - const run $ packages $ verbose $ packages_dir $ odoc_dir $ odocl_dir - $ index_dir $ mld_dir $ html_dir $ stats $ nb_workers $ odoc_bin $ voodoo - $ package_name $ blessed $ dune_style $ compile_grep $ link_grep - $ generate_grep) + Cmd.group info [ Voodoo_mode.cmd; Dune_mode.cmd; Opam_mode.cmd ] (* let map = Ocamlfind.package_to_dir_map () in let _dirs = List.map (fun lib -> List.assoc lib map) deps in From a1a6e82132e7f613dc3cc0369d5ecf38a0e6ea49 Mon Sep 17 00:00:00 2001 From: Guillaume Petiot Date: Fri, 8 Nov 2024 12:13:47 +0000 Subject: [PATCH 2/4] Update src/driver/odoc_driver.ml MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Co-authored-by: Paul-Elliot Anglès d'Auriac --- src/driver/odoc_driver.ml | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/driver/odoc_driver.ml b/src/driver/odoc_driver.ml index 1809659d88..05b320b735 100644 --- a/src/driver/odoc_driver.ml +++ b/src/driver/odoc_driver.ml @@ -694,7 +694,10 @@ module Dune_mode = struct Arg.(value & pos 0 Common_args.fpath_arg (Fpath.v ".") & info []) let cmd = - let doc = "Dune mode" in + let doc = + "Dune mode, which builds the documentation of the local libraries of a \ + dune project." + in let info = Cmd.info "dune" ~doc in Cmd.v info Term.(const run $ dune_style $ Common_args.term) end From 1f44852811a99d56d1f55ce897bbacba2420347d Mon Sep 17 00:00:00 2001 From: Guillaume Petiot Date: Fri, 8 Nov 2024 12:23:41 +0000 Subject: [PATCH 3/4] Arg 'blessed' is only used in voodoo mode --- src/driver/common_args.ml | 7 ------- src/driver/odoc_driver.ml | 13 ++++++++----- 2 files changed, 8 insertions(+), 12 deletions(-) diff --git a/src/driver/common_args.ml b/src/driver/common_args.ml index 9cdd441bf5..26355f68f2 100644 --- a/src/driver/common_args.ml +++ b/src/driver/common_args.ml @@ -45,10 +45,6 @@ let odoc_bin = let doc = "Odoc binary to use" in Arg.(value & opt (some string) None & info [ "odoc" ] ~doc) -let blessed = - let doc = "Blessed" in - Arg.(value & flag & info [ "blessed" ] ~doc) - let compile_grep = let doc = "Show compile commands containing the string" in Arg.(value & opt (some string) None & info [ "compile-grep" ] ~doc) @@ -72,7 +68,6 @@ type t = { stats : bool; nb_workers : int; odoc_bin : string option; - blessed : bool; compile_grep : string option; link_grep : string option; generate_grep : string option; @@ -92,7 +87,6 @@ let term = and+ stats = stats and+ nb_workers = nb_workers and+ odoc_bin = odoc_bin - and+ blessed = blessed and+ compile_grep = compile_grep and+ link_grep = link_grep and+ generate_grep = generate_grep in @@ -107,7 +101,6 @@ let term = stats; nb_workers; odoc_bin; - blessed; compile_grep; link_grep; generate_grep; diff --git a/src/driver/odoc_driver.ml b/src/driver/odoc_driver.ml index 05b320b735..e0b31bc5a9 100644 --- a/src/driver/odoc_driver.ml +++ b/src/driver/odoc_driver.ml @@ -552,7 +552,7 @@ let remap_virtual_interfaces duplicate_hashes pkgs = pkgs type mode = - | Voodoo of { package_name : string } + | Voodoo of { package_name : string; blessed : bool } | Dune of { path : Fpath.t } | Opam of { packages_dir : Fpath.t option } @@ -568,7 +568,6 @@ let run mode stats; nb_workers; odoc_bin; - blessed; compile_grep; link_grep; generate_grep; @@ -584,7 +583,7 @@ let run mode let all, extra_libs_paths = match mode with - | Voodoo { package_name = p } -> + | Voodoo { package_name = p; blessed } -> let all = Voodoo.of_voodoo p ~blessed in let extra_libs_paths = Voodoo.extra_libs_paths odoc_dir in (all, extra_libs_paths) @@ -675,16 +674,20 @@ let run mode if stats then Stats.bench_results html_dir module Voodoo_mode = struct - let run package_name = run (Voodoo { package_name }) + let run package_name blessed = run (Voodoo { package_name; blessed }) let package_name = let doc = "Name of package to process with voodoo" in Arg.(value & pos 0 string "" & info [] ~doc) + let blessed = + let doc = "Blessed" in + Arg.(value & flag & info [ "blessed" ] ~doc) + let cmd = let doc = "Process output from voodoo-prep" in let info = Cmd.info "voodoo" ~doc in - Cmd.v info Term.(const run $ package_name $ Common_args.term) + Cmd.v info Term.(const run $ package_name $ blessed $ Common_args.term) end module Dune_mode = struct From bbb67d7ef10603e3f93fbe1197b5dbde19cf3ab8 Mon Sep 17 00:00:00 2001 From: Guillaume Petiot Date: Fri, 8 Nov 2024 12:28:57 +0000 Subject: [PATCH 4/4] Arg 'packages' is only used in opam mode --- src/driver/common_args.ml | 10 +--------- src/driver/odoc_driver.ml | 16 ++++++++++------ 2 files changed, 11 insertions(+), 15 deletions(-) diff --git a/src/driver/common_args.ml b/src/driver/common_args.ml index 26355f68f2..1aea27f7e4 100644 --- a/src/driver/common_args.ml +++ b/src/driver/common_args.ml @@ -24,11 +24,6 @@ let html_dir = let doc = "Directory in which the generated HTML files go" in Arg.(value & opt fpath_arg (Fpath.v "_html/") & info [ "html-dir" ] ~doc) -let packages = - (* TODO: Is it package or library? *) - let doc = "The packages to document" in - Arg.(value & opt_all string [] & info [ "p" ] ~doc) - let verbose = let doc = "Enable verbose output" in Arg.(value & flag & info [ "v"; "verbose" ] ~doc) @@ -58,7 +53,6 @@ let generate_grep = Arg.(value & opt (some string) None & info [ "html-grep" ] ~doc) type t = { - packages : string list; verbose : bool; odoc_dir : Fpath.t; odocl_dir : Fpath.t option; @@ -77,8 +71,7 @@ let term = let open Term in let ( let+ ) t f = const f $ t in let ( and+ ) a b = const (fun x y -> (x, y)) $ a $ b in - let+ packages = packages - and+ verbose = verbose + let+ verbose = verbose and+ odoc_dir = odoc_dir and+ odocl_dir = odocl_dir and+ index_dir = index_dir @@ -91,7 +84,6 @@ let term = and+ link_grep = link_grep and+ generate_grep = generate_grep in { - packages; verbose; odoc_dir; odocl_dir; diff --git a/src/driver/odoc_driver.ml b/src/driver/odoc_driver.ml index e0b31bc5a9..0dd1270e14 100644 --- a/src/driver/odoc_driver.ml +++ b/src/driver/odoc_driver.ml @@ -554,12 +554,11 @@ let remap_virtual_interfaces duplicate_hashes pkgs = type mode = | Voodoo of { package_name : string; blessed : bool } | Dune of { path : Fpath.t } - | Opam of { packages_dir : Fpath.t option } + | Opam of { packages : string list; packages_dir : Fpath.t option } let run mode { - Common_args.packages; - verbose; + Common_args.verbose; odoc_dir; odocl_dir; index_dir; @@ -588,7 +587,7 @@ let run mode let extra_libs_paths = Voodoo.extra_libs_paths odoc_dir in (all, extra_libs_paths) | Dune { path } -> (Dune_style.of_dune_build path, Util.StringMap.empty) - | Opam { packages_dir } -> + | Opam { packages; packages_dir } -> let libs = if packages = [] then Ocamlfind.all () else packages in let libs = List.map Ocamlfind.sub_libraries libs @@ -706,7 +705,12 @@ module Dune_mode = struct end module Opam_mode = struct - let run packages_dir = run (Opam { packages_dir }) + let run packages packages_dir = run (Opam { packages; packages_dir }) + + let packages = + (* TODO: Is it package or library? *) + let doc = "The packages to document" in + Arg.(value & opt_all string [] & info [ "p" ] ~doc) let packages_dir = let doc = "Packages directory under which packages should be output." in @@ -718,7 +722,7 @@ module Opam_mode = struct let cmd = let doc = "Opam mode" in let info = Cmd.info "opam" ~doc in - Cmd.v info Term.(const run $ packages_dir $ Common_args.term) + Cmd.v info Term.(const run $ packages $ packages_dir $ Common_args.term) end let cmd =