Skip to content

Commit

Permalink
fix(metrics): output correct process metrics
Browse files Browse the repository at this point in the history
Before this commit we would output an "async" start event when a process
awould start nd then a "complete" event when it would be finished.

The "async" start event is unnecessary and this commit removes it. All
the information recorded in the "async" start event is therefore moved
to the complete event.

The new output is now properly displayed by the various visualization
tools (perfetto, chrome)

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

<!-- ps-id: d5f448b8-a896-4612-bc4e-e8d16c41fc51 -->
  • Loading branch information
rgrinberg committed Jan 16, 2023
1 parent 0972be8 commit 2ee9dbb
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 29 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
Unreleased
----------

- Fix `--trace-file` output. Dune now emits a single *complete* event for every
executed process. Unterminated *async* events are no longer written. (#6892,
@rgrinberg)

- Fix preprocessing with `staged_pps` (#6748, fixes #6644, @rgrinberg)

- Make `dune describe workspace` return consistent dependencies for
Expand Down
47 changes: 18 additions & 29 deletions src/dune_engine/process.ml
Original file line number Diff line number Diff line change
Expand Up @@ -577,29 +577,22 @@ end = struct
fail ~loc ~annots paragraphs
end

let report_process_start stats ~metadata ~id ~pid ~prog ~args ~now =
let report_process_finished stats ~metadata ~prog ~pid ~args ~started_at
(times : Proc.Times.t) =
let common =
let name =
match metadata.name with
| Some n -> n
| None -> Filename.basename prog
in
let ts = Timestamp.of_float_seconds now in
let ts = Timestamp.of_float_seconds started_at in
Event.common_fields ~cat:("process" :: metadata.categories) ~name ~ts ()
in
let args =
[ ("process_args", `List (List.map args ~f:(fun arg -> `String arg)))
; ("pid", `Int (Pid.to_int pid))
]
in
let event =
Event.async (Chrome_trace.Id.create (`Int id)) ~args Start common
in
Dune_stats.emit stats event;
(common, args)

let report_process_end stats (common, args) ~now (times : Proc.Times.t) =
let common = Event.set_ts common (Timestamp.of_float_seconds now) in
let dur = Event.Timestamp.of_float_seconds times.elapsed_time in
let event = Event.complete ~args ~dur common in
Dune_stats.emit stats event
Expand Down Expand Up @@ -692,7 +685,7 @@ let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr)
(stdout, stderr)
| _ -> ((`No_capture, stdout_to), (`No_capture, stderr_to))
in
let event_common, started_at, pid =
let started_at, pid =
(* Output.fd might create the file with Unix.openfile. We need to make
sure to call it before doing the chdir as the path might be
relative. *)
Expand All @@ -705,26 +698,21 @@ let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr)
| false -> env
in
let env = Env.to_unix env |> Spawn.Env.of_list in
let started_at, pid =
let started_at =
(* jeremiedimino: I think we should do this just before the [execve]
in the stub for [Spawn.spawn] to be as precise as possible *)
let now = Unix.gettimeofday () in
( now
, Spawn.spawn () ~prog:prog_str ~argv ~env ~stdout ~stderr ~stdin
~setpgid:Spawn.Pgid.new_process_group
~cwd:
(match dir with
| None -> Inherit
| Some dir -> Path (Path.to_string dir))
|> Pid.of_int )
Unix.gettimeofday ()
in
let event_common =
Option.map config.stats ~f:(fun stats ->
( stats
, report_process_start stats ~metadata ~id ~pid ~prog:prog_str
~args ~now:started_at ))
let pid =
Spawn.spawn () ~prog:prog_str ~argv ~env ~stdout ~stderr ~stdin
~setpgid:Spawn.Pgid.new_process_group
~cwd:
(match dir with
| None -> Inherit
| Some dir -> Path (Path.to_string dir))
|> Pid.of_int
in
(event_common, started_at, pid)
(started_at, pid)
in
Io.release stdout_to;
Io.release stderr_to;
Expand All @@ -736,8 +724,9 @@ let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr)
; resource_usage = process_info.resource_usage
}
in
Option.iter event_common ~f:(fun (stats, common) ->
report_process_end stats common ~now:process_info.end_time times);
Option.iter config.stats ~f:(fun stats ->
report_process_finished stats ~metadata ~prog:prog_str ~pid ~args
~started_at times);
Option.iter response_file ~f:Path.unlink;
let actual_stdout =
match stdout_capture with
Expand Down

0 comments on commit 2ee9dbb

Please sign in to comment.