@@ -525,6 +525,7 @@ module At_rev = struct
525
525
{ repo : repo
526
526
; revision : Object .t
527
527
; files : File.Set .t
528
+ ; recursive_directory_entries : File.Set .t Path.Local.Table .t
528
529
}
529
530
530
531
let equal x y = Object. equal x.revision y.revision
@@ -684,25 +685,46 @@ module At_rev = struct
684
685
>> | List. cons files
685
686
>> | File.Set. union_all
686
687
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 }
688
719
;;
689
720
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
+ ;;
691
724
692
725
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
706
728
;;
707
729
708
730
let directory_entries_immediate t path =
@@ -721,7 +743,10 @@ module At_rev = struct
721
743
path
722
744
;;
723
745
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
+ =
725
750
(* TODO iterate over submodules to output sources *)
726
751
let git = Lazy. force Vcs. git in
727
752
let temp_dir = Temp_dir. dir_for_target ~target ~prefix: " rev-store" ~suffix: rev in
0 commit comments