Skip to content

Commit

Permalink
more tracing
Browse files Browse the repository at this point in the history
  • Loading branch information
c-cube committed Dec 7, 2023
1 parent 88e3649 commit f274476
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 8 deletions.
1 change: 1 addition & 0 deletions src/client/opamAuxCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -395,6 +395,7 @@ let simulate_local_pinnings ?quiet ?(for_view=false) st to_pin =

let simulate_autopin st ?quiet ?(for_view=false) ?locked ?recurse ?subpath
atom_or_local_list =
OpamTrace.with_span "AuxCommands.simulate_autopin" @@ fun () ->
let atoms, to_pin, obsolete_pins, already_pinned_set =
autopin_aux st ?quiet ~for_view ?recurse ?subpath ?locked atom_or_local_list
in
Expand Down
1 change: 1 addition & 0 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -935,6 +935,7 @@ let show cli =
let show global_options fields show_empty raw where
list_files file normalise no_lint just_file all_versions sort atom_locs
() =
OpamTrace.with_span "Commands.show" @@ fun () ->
let print_just_file opamf opam =
if not no_lint then OpamFile.OPAM.print_errors opam;
let opam =
Expand Down
1 change: 1 addition & 0 deletions src/client/opamListCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -715,6 +715,7 @@ let display st format packages =
OpamConsole.print_table ?cut:format.wrap stdout ~sep:format.separator

let get_switch_state gt rt =
OpamTrace.with_span "ListCommand.get_switch_state" @@ fun () ->
match OpamStateConfig.get_switch_opt () with
| None -> OpamSwitchState.load_virtual gt rt
| Some sw -> OpamSwitchState.load `Lock_none gt rt sw
Expand Down
8 changes: 6 additions & 2 deletions src/core/opamProcess.ml
Original file line number Diff line number Diff line change
Expand Up @@ -501,7 +501,7 @@ let empty_result = {

(* XXX: the function might block for ever for some channels kinds *)
let read_lines f =
OpamTrace.with_span "process.read_lines"
OpamTrace.with_span "Process.read_lines"
~data:["f", `String f] @@ fun () ->
try
let ic = open_in f in
Expand Down Expand Up @@ -756,7 +756,11 @@ let dry_wait_one = function
| _ -> raise (Invalid_argument "dry_wait_one")

let run command =
OpamTrace.with_span "process.run" ~data:["cmd", `String command.cmd] @@ fun () ->
OpamTrace.with_span "Process.run"
~data:["cmd", `String command.cmd;
"args", `String (String.concat " " command.args)]
@@ fun () ->

let command =
{ command with
cmd_stdin = OpamStd.Option.Op.(command.cmd_stdin ++ Some (not Sys.win32)) }
Expand Down
17 changes: 11 additions & 6 deletions src/state/opamSysInteract.ml
Original file line number Diff line number Diff line change
Expand Up @@ -380,7 +380,7 @@ let yum_cmd = lazy begin
end

let packages_status ?(env=OpamVariable.Map.empty) config packages =
OpamTrace.with_span "sys-interact.packages-status" @@ fun () ->
OpamTrace.with_span "sys-interact.packages_status" @@ fun () ->
let (+++) pkg set = OpamSysPkg.Set.add (OpamSysPkg.of_string pkg) set in
(* Some package managers don't permit to request on available packages. In
this case, we consider all non installed packages as [available]. *)
Expand Down Expand Up @@ -470,7 +470,7 @@ let packages_status ?(env=OpamVariable.Map.empty) config packages =
in
let compute_sets_for_arch ~pacman =
let get_avail_w_virtuals () =
OpamTrace.with_span "comput-sets-for-archs" @@ fun () ->
OpamTrace.with_span "SysInteract.compute-sets-for-archs" @@ fun () ->
let package_provided str =
OpamSysPkg.of_string
(match OpamStd.String.cut_at str '=' with
Expand All @@ -496,9 +496,12 @@ let packages_status ?(env=OpamVariable.Map.empty) config packages =
*)
(* Discard stderr to not have it pollute output. Plus, exit code is the
number of packages not found. *)
run_command ~discard_err:true pacman ["-Si"]
|> snd
|> List.fold_left (fun (avail, provides, latest) l ->
let _, p = run_command ~discard_err:true pacman ["-Si"] in

OpamTrace.with_span "parse_pacman_output"
~data:["n", `Float (float_of_int (List.length p))]
@@ fun () ->
List.fold_left (fun (avail, provides, latest) l ->
match OpamStd.String.split l ' ' with
| "Name"::":"::p::_ ->
p +++ avail, provides, Some (OpamSysPkg.of_string p)
Expand All @@ -512,7 +515,7 @@ let packages_status ?(env=OpamVariable.Map.empty) config packages =
in
ps ++ avail, provides, None
| _ -> avail, provides, latest)
(OpamSysPkg.Set.empty, OpamSysPkg.Map.empty, None)
(OpamSysPkg.Set.empty, OpamSysPkg.Map.empty, None) p
|> (fun (a,p,_) -> a,p)
in
let get_installed str_pkgs =
Expand All @@ -522,6 +525,8 @@ let packages_status ?(env=OpamVariable.Map.empty) config packages =
>extra/cmark 0.29.0-1
> CommonMark parsing and rendering library and program in C
*)
OpamTrace.with_span "SysInteract.get_installed" @@ fun () ->

let re_pkg =
Re.(compile @@ seq
[ bol;
Expand Down

0 comments on commit f274476

Please sign in to comment.