Skip to content

Commit 30ee6ac

Browse files
authored
pkg: precompute directory descendants in rev_store (#11254)
Previously dune would do a linear search through all files in the rev store in order to compute the descendants of a single directory. This change precomputes all descendants of each directory in a single pass. Signed-off-by: Stephen Sherratt <[email protected]>
1 parent 6152ab8 commit 30ee6ac

File tree

2 files changed

+43
-16
lines changed

2 files changed

+43
-16
lines changed

otherlibs/stdune/src/path.mli

+2
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,8 @@ module Local : sig
6666
val split_first_component : t -> (Filename.t * t) option
6767
val explode : t -> Filename.t list
6868
val descendant : t -> of_:t -> t option
69+
70+
module Table : Hashtbl.S with type key = t
6971
end
7072

7173
module External : sig

src/dune_pkg/rev_store.ml

+41-16
Original file line numberDiff line numberDiff line change
@@ -525,6 +525,7 @@ module At_rev = struct
525525
{ repo : repo
526526
; revision : Object.t
527527
; files : File.Set.t
528+
; recursive_directory_entries : File.Set.t Path.Local.Table.t
528529
}
529530

530531
let equal x y = Object.equal x.revision y.revision
@@ -684,25 +685,46 @@ module At_rev = struct
684685
>>| List.cons files
685686
>>| File.Set.union_all
686687
in
687-
{ repo; revision; files }
688+
let recursive_directory_entries =
689+
let recursive_directory_entries =
690+
Path.Local.Table.create (File.Set.cardinal files)
691+
in
692+
(* Build a table mapping each directory path to the set of files under it
693+
in the directory hierarchy. *)
694+
File.Set.iter files ~f:(fun file ->
695+
(* Add [file] to the set of files under each directory which is an
696+
ancestor of [file]. *)
697+
let rec loop = function
698+
| None -> ()
699+
| Some parent ->
700+
let recursive_directory_entries_of_parent =
701+
Path.Local.Table.find_or_add
702+
recursive_directory_entries
703+
parent
704+
~f:(Fun.const File.Set.empty)
705+
in
706+
let recursive_directory_entries_of_parent =
707+
File.Set.add recursive_directory_entries_of_parent file
708+
in
709+
Path.Local.Table.set
710+
recursive_directory_entries
711+
parent
712+
recursive_directory_entries_of_parent;
713+
loop (Path.Local.parent parent)
714+
in
715+
loop (File.path file |> Path.Local.parent));
716+
recursive_directory_entries
717+
in
718+
{ repo; revision; files; recursive_directory_entries }
688719
;;
689720

690-
let content { repo; revision; files = _ } path = show repo [ `Path (revision, path) ]
721+
let content { repo; revision; files = _; recursive_directory_entries = _ } path =
722+
show repo [ `Path (revision, path) ]
723+
;;
691724

692725
let directory_entries_recursive t path =
693-
(* TODO: there are much better ways of implementing this:
694-
1. using libgit or ocamlgit
695-
2. possibly using [$ git archive] *)
696-
File.Set.to_list t.files
697-
|> List.filter_map ~f:(fun (file : File.t) ->
698-
let file_path = File.path file in
699-
(* [directory_entries "foo"] shouldn't return "foo" as an entry, but
700-
"foo" is indeed a descendant of itself. So we filter it manually. *)
701-
if (not (Path.Local.equal file_path path))
702-
&& Path.Local.is_descendant file_path ~of_:path
703-
then Some file
704-
else None)
705-
|> File.Set.of_list
726+
Path.Local.Table.find t.recursive_directory_entries path
727+
|> Option.value ~default:File.Set.empty
706728
;;
707729

708730
let directory_entries_immediate t path =
@@ -721,7 +743,10 @@ module At_rev = struct
721743
path
722744
;;
723745

724-
let check_out { repo = { dir; _ }; revision = Sha1 rev; files = _ } ~target =
746+
let check_out
747+
{ repo = { dir; _ }; revision = Sha1 rev; files = _; recursive_directory_entries = _ }
748+
~target
749+
=
725750
(* TODO iterate over submodules to output sources *)
726751
let git = Lazy.force Vcs.git in
727752
let temp_dir = Temp_dir.dir_for_target ~target ~prefix:"rev-store" ~suffix:rev in

0 commit comments

Comments
 (0)