Skip to content

Commit

Permalink
Driver: add debugging utilities
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd authored and jonludlam committed Oct 3, 2024
1 parent f9a34e4 commit 262e509
Showing 1 changed file with 26 additions and 2 deletions.
28 changes: 26 additions & 2 deletions src/driver/odoc_driver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -516,7 +516,8 @@ let render_stats env nprocs =
inner (0, 0, 0, 0, 0, 0, 0, 0, 0, 0))

let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
odoc_bin voodoo package_name blessed dune_style =
odoc_bin voodoo package_name blessed dune_style 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 ->
Expand Down Expand Up @@ -582,6 +583,17 @@ let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
(fun () -> render_stats env nb_workers)
in

let grep_log l s =
let open Astring in
let do_ affix =
let grep l = if String.is_infix ~affix l then Format.printf "%s\n" l in
List.iter grep l
in
Option.iter do_ s
in
grep_log !Cmd_outputs.compile_output compile_grep;
grep_log !Cmd_outputs.link_output link_grep;
grep_log !Cmd_outputs.generate_output generate_grep;
Format.eprintf "Final stats: %a@.%!" Stats.pp_stats Stats.stats;
Format.eprintf "Total time: %f@.%!" (Stats.total_time ());
if stats then Stats.bench_results html_dir
Expand Down Expand Up @@ -643,14 +655,26 @@ 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 = "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
$ html_dir $ stats $ nb_workers $ odoc_bin $ voodoo $ package_name
$ blessed $ dune_style)
$ blessed $ dune_style $ compile_grep $ link_grep $ generate_grep)

(* let map = Ocamlfind.package_to_dir_map () in
let _dirs = List.map (fun lib -> List.assoc lib map) deps in
Expand Down

0 comments on commit 262e509

Please sign in to comment.