Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 5 additions & 1 deletion bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1404,7 +1404,11 @@ let init_with_root ~(root : Workspace_root.t) (builder : Builder.t) =
];
Dune_console.separate_messages c.builder.separate_error_messages;
Option.iter c.stats ~f:(fun stats ->
let event = Dune_trace.Event.config () in
let event =
Dune_trace.Event.config
~version:
(Build_info.V1.version () |> Option.map ~f:Build_info.V1.Version.to_string)
in
Dune_trace.emit stats event);
(* Setup hook for printing GC stats to a file *)
at_exit (fun () ->
Expand Down
2 changes: 2 additions & 0 deletions doc/changes/added/12908.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- Add `argv`, the process environment, and the dune version to the config event
in the trace (#12909, @rgrinberg)
15 changes: 12 additions & 3 deletions src/dune_trace/dune_trace.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
open Stdune
module Timestamp = Chrome_trace.Event.Timestamp
module Json = Json

module Mac = struct
external open_fds : pid:int -> int = "dune_trace_open_fds"
Expand Down Expand Up @@ -135,9 +134,19 @@ module Event = struct
Event.counter common args
;;

let config () =
let config ~version =
let args =
let args =
[ "build_dir", `String (Path.Build.to_string Path.Build.root)
; "argv", `List (Array.to_list Sys.argv |> List.map ~f:Json.string)
; "env", `List (Unix.environment () |> Array.to_list |> List.map ~f:Json.string)
]
in
match version with
| None -> args
| Some v -> ("version", Stdune.Json.string v) :: args
in
let open Chrome_trace in
let args = [ "build_dir", `String (Path.Build.to_string Path.Build.root) ] in
let ts = Event.Timestamp.of_float_seconds (Unix.gettimeofday ()) in
let common = Event.common_fields ~cat:[ "config" ] ~name:"config" ~ts () in
Event.instant ~args common
Expand Down
2 changes: 1 addition & 1 deletion src/dune_trace/dune_trace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ module Event : sig

val scan_source : name:string -> start:float -> stop:float -> dir:Path.Source.t -> t
val scheduler_idle : unit -> t
val config : unit -> t
val config : version:string option -> t

module Rpc : sig
type stage =
Expand Down
Loading