Skip to content

Commit

Permalink
driver: Record execution time of every commands
Browse files Browse the repository at this point in the history
The result is written into a current-bench's JSON format and promoted by

    dune build @bench
  • Loading branch information
Julow committed Jun 26, 2023
1 parent 121d964 commit 845c9d2
Show file tree
Hide file tree
Showing 3 changed files with 99 additions and 13 deletions.
81 changes: 77 additions & 4 deletions doc/driver.mld
Original file line number Diff line number Diff line change
Expand Up @@ -155,12 +155,15 @@ let link_output = ref [ "" ]

let generate_output = ref [ "" ]

(* Record the commands executed and their running time. *)
let commands = ref [ ]

let run cmd =
let cmd_str = Cmd.to_string cmd in
commands := cmd_str :: !commands;
OS.Cmd.(run_out ~err:OS.Cmd.err_run_out cmd |> to_lines) |> get_ok
let t_start = Sys.time () in
let r = OS.Cmd.(run_out ~err:OS.Cmd.err_run_out cmd |> to_lines) |> get_ok in
let t_end = Sys.time () in
commands := (cmd, t_end -. t_start) :: !commands;
r

let add_prefixed_output cmd list prefix lines =
if List.length lines > 0 then
Expand Down Expand Up @@ -708,7 +711,7 @@ html/odoc/odoc_html/Odoc_html/Types/index.html
Finally, let's have a list of all of the commands executed during the execution of this process:

{[
# List.iter (Printf.printf "$ %s\n") (List.rev !commands);;
# List.iter (fun (cmd, _) -> Printf.printf "$ %s\n" (Cmd.to_string cmd)) (List.rev !commands);;
$ 'ocamlfind' 'query' 'yojson'
$ 'ocamlfind' 'query' 'stdlib'
$ 'ocamlfind' 'query' 'fmt'
Expand Down Expand Up @@ -2785,3 +2788,73 @@ $ '../src/odoc/bin/main.exe' 'html-generate' 'page-ocamldoc_differences.odocl' '
$ '../src/odoc/bin/main.exe' 'support-files' '-o' 'html/odoc'
- : unit = ()
]}

This last block analyze the running times so that they can be submitted to
{{:https://github.com/ocurrent/current-bench}current-bench}.

{[
(* *)
#require "yojson" ;;

let compute_metric_cmd cmd =
let rec compute min_ max_ total count = function
| [] -> (min_, max_, total /. float count, count)
| (_, t) :: tl ->
compute (min min_ t) (max max_ t) (total +. t) (count + 1) tl
in
let filtered_commands =
List.filter
(fun (cmd', _) ->
match Bos.Cmd.to_list cmd' with
| _ :: cmd' :: _ -> cmd = cmd'
| _ -> false)
!commands
in
match filtered_commands with
| [] -> []
| (_, time) :: tl ->
let min, max, avg, count = compute time time time 1 tl in
[
`Assoc
[
("name", `String ("total-" ^ cmd));
("value", `Int count);
( "description",
`String ("Number of time 'odoc " ^ cmd ^ "' has run.") );
];
`Assoc
[
("name", `String ("time-" ^ cmd));
( "value",
`Assoc
[
("min", `Float min); ("max", `Float max); ("avg", `Float avg);
] );
("units", `String "s");
("description", `String ("Time taken by 'odoc " ^ cmd ^ "'"));
("trend", `String "lower-is-better");
];
]

let metrics =
compute_metric_cmd "compile"
@ compute_metric_cmd "compile-deps"
@ compute_metric_cmd "link"
@ compute_metric_cmd "html-generate"

let bench_results =
`Assoc
[
("name", `String "odoc");
( "results",
`List
[
`Assoc
[ ("name", `String "driver.mld"); ("metrics", `List metrics) ];
] );
]

(* Save the result in a file. This file won't be promoted into the
documentation. *)
let () = Yojson.to_file "driver-benchmarks.json" bench_results
]}
26 changes: 17 additions & 9 deletions doc/dune
Original file line number Diff line number Diff line change
Expand Up @@ -22,17 +22,25 @@
; odoc_for_authors.mld
; parent_child_spec.mld))

; The driver is also used to collect benchmarks. The benchmark result is always
; generated but is promoted only by the @bench alias.
(rule
(alias docgen)
(deps
(:x driver.mld)
(glob_files *.ml*)
(glob_files *.png)
(glob_files library_mlds/*.mld)
(package odoc))
(targets driver.mld.corrected driver-benchmarks.json)
(enabled_if
(> %{ocaml_version} 4.11))
(deps
(glob_files *.mld)
(glob_files library_mlds/*)
(glob_files examples/*.ml*))
(action
(progn
; Make sure the benchmark result is created as Dune would not show the diff
; if the script failed before creating it.
(write-file driver-benchmarks.json "")
(run ocaml-mdx-test --force-output %{dep:driver.mld}))))

(rule
(alias docgen)
(action
(progn
(run ocaml-mdx-test %{x})
(diff? %{x} %{x}.corrected))))
(diff driver.mld driver.mld.corrected))))
5 changes: 5 additions & 0 deletions dune
Original file line number Diff line number Diff line change
Expand Up @@ -8,3 +8,8 @@
(release
(flags
(:standard -g -w -18-53))))

(rule
(alias bench)
(action
(diff driver-benchmarks.json doc/driver-benchmarks.json)))

0 comments on commit 845c9d2

Please sign in to comment.