@@ -717,6 +717,13 @@ module Entry = struct
717717end
718718
719719let fetch_allow_failure repo ~url obj =
720+ let open Dune_stats.Fiber.O in
721+ let & () =
722+ { Dune_stats. name = " fetch"
723+ ; cat = [ " rev_store" ]
724+ ; args = [ " url" , `String url; " object" , `String (Object. to_hex obj) ]
725+ }
726+ in
720727 with_mutex repo obj ~f: (fun () ->
721728 object_exists repo obj
722729 >> = function
@@ -922,12 +929,19 @@ module At_rev = struct
922929 ;;
923930
924931 let rec of_rev repo ~revision =
932+ let open Dune_stats.Fiber.O in
933+ let & () =
934+ { Dune_stats. name = " of_rev"
935+ ; cat = [ " rev_store" ]
936+ ; args = [ " revision" , `String (Object. to_hex revision) ]
937+ }
938+ in
925939 let * files, submodules = files_and_submodules repo revision in
926940 let commit_paths = path_commit_map submodules in
927941 let + files =
928942 let * submodules = Submodule. parse repo revision in
929943 (* It's not safe to do a parallel map because adding a remote
930- requires getting the lock (which we're now holding) *)
944+ requires getting the lock (which we're now holding) *)
931945 Fiber. sequential_map submodules ~f: (fun { Submodule. path; source } ->
932946 match Path.Local.Map. find commit_paths path with
933947 | None ->
@@ -956,10 +970,10 @@ module At_rev = struct
956970 Path.Local.Table. create (File.Set. cardinal files)
957971 in
958972 (* Build a table mapping each directory path to the set of files under it
959- in the directory hierarchy. *)
973+ in the directory hierarchy. *)
960974 File.Set. iter files ~f: (fun file ->
961975 (* Add [file] to the set of files under each directory which is an
962- ancestor of [file]. *)
976+ ancestor of [file]. *)
963977 let rec loop = function
964978 | None -> ()
965979 | Some parent ->
@@ -1021,6 +1035,16 @@ module At_rev = struct
10211035 }
10221036 ~target
10231037 =
1038+ let open Dune_stats.Fiber.O in
1039+ let & () =
1040+ { Dune_stats. name = " check_out"
1041+ ; cat = [ " rev_store" ]
1042+ ; args =
1043+ [ " revision" , `String (Object. to_hex revision)
1044+ ; " target" , `String (Path. to_string target)
1045+ ]
1046+ }
1047+ in
10241048 let git = Lazy. force Vcs. git in
10251049 let temp_dir =
10261050 Temp_dir. dir_for_target ~target ~prefix: " rev-store" ~suffix: (Object. to_hex revision)
@@ -1045,11 +1069,11 @@ module At_rev = struct
10451069 path, archive)
10461070 in
10471071 (* We untar things into a temp dir to make sure we don't create garbage
1048- in the build dir until we know can produce the files *)
1072+ in the build dir until we know can produce the files *)
10491073 let target_in_temp_dir = Path. relative temp_dir " dir" in
10501074 let + () =
10511075 (* We don't necessarily need to unpack things sequentially, but it's the
1052- easiest thing to do *)
1076+ easiest thing to do *)
10531077 Fiber. sequential_iter archives ~f: (fun (path , archive ) ->
10541078 let target_in_temp_dir = Path. append_local target_in_temp_dir path in
10551079 Archive_driver. extract Archive_driver. tar ~archive ~target: target_in_temp_dir
0 commit comments