@@ -130,7 +130,7 @@ module type Rec = sig
130130 val build_alias : Alias .t -> Dep.Fact.Files .t Memo .t
131131
132132 val build_file : Path .t -> Digest .t Memo .t
133- val build_dir : Path .t -> ( Digest .t * Digest .t Targets.Produced .t ) Memo .t
133+ val build_dir : Path .t -> Digest .t Targets.Produced .t Memo .t
134134 val build_dep : Dep .t -> Dep.Fact .t Memo .t
135135 val build_deps : Dep.Set .t -> Dep.Facts .t Memo .t
136136 val execute_rule : Rule .t -> rule_execution_result Memo .t
@@ -227,7 +227,7 @@ end = struct
227227
228228 (* The current version of the rule digest scheme. We should increment it when
229229 making any changes to the scheme, to avoid collisions. *)
230- let rule_digest_version = 20
230+ let rule_digest_version = 21
231231
232232 let compute_rule_digest
233233 (rule : Rule.t )
@@ -681,6 +681,10 @@ end = struct
681681 execute_action_generic_stage2_impl
682682 ;;
683683
684+ (* The current version of the action digest scheme. We should increment it when
685+ making any changes to the scheme, to avoid collisions. *)
686+ let action_digest_version = 1
687+
684688 let execute_action_generic
685689 ~observing_facts
686690 (act : Rule.Anonymous_action.t )
@@ -737,7 +741,8 @@ end = struct
737741 |> Env.Map. to_list
738742 in
739743 Digest. generic
740- ( env
744+ ( action_digest_version
745+ , env
741746 , Dep.Set. digest deps
742747 , Action. for_shell action
743748 , List. map locks ~f: Path. to_string
@@ -768,6 +773,10 @@ end = struct
768773 Io. read_file (Path. build target)
769774 ;;
770775
776+ (* CR-soon amokhov: Instead of wrapping the result into a variant, [build_file_impl]
777+ could always return [targets : Digest.t Targets.Produced.t], and the latter could
778+ provide a way to conveniently check if a specific [path] is a file or a directory,
779+ as well as extract its digest when needed. *)
771780 type target_kind =
772781 | File_target
773782 | Dir_target of
@@ -800,6 +809,13 @@ end = struct
800809 (match Targets.Produced. find targets path with
801810 | Some digest -> digest, File_target
802811 | None ->
812+ (* CR-soon amokhov: Here we expect [path] to be a directory target. It seems odd
813+ to compute its digest here by calling to [Cached_digest.build_file]. Shouldn't
814+ we do that in [execute_rule], like we do for file targets?
815+
816+ rleshchinskiy: Is this digest ever used? [build_dir] discards it and do we
817+ (or should we) ever use [build_file] to build directories? Perhaps this could
818+ be split in two memo tables, one for files and one for directories. *)
803819 (match Cached_digest. build_file ~allow_dirs: true path with
804820 | Ok digest -> digest, Dir_target { targets }
805821 (* Must be a directory target *)
@@ -883,21 +899,18 @@ end = struct
883899 let + digest = build_file path in
884900 path, digest)
885901 in
886- Dep.Fact.Files. make ~files: (Path.Map. of_list_exn files) ~dirs: Path.Map. empty
887- | Build_under_directory_target _ ->
888- let * digest, path_map = build_dir dir in
889- let files =
890- let dir = Path. as_in_build_dir_exn dir in
891- match Targets.Produced. find_dir path_map dir with
892- | Some files ->
893- Filename.Map. to_list_map files ~f: (fun file digest ->
894- Path. build (Path.Build. relative dir file), digest)
895- |> List. filter ~f: (fun (path , _ ) -> File_selector. test g path)
896- |> Path.Map. of_list_exn
897- | None -> Path.Map. empty
898- in
899- let dirs = Path.Map. singleton dir digest in
900- Memo. return (Dep.Fact.Files. make ~files ~dirs )
902+ Dep.Fact.Files. create ?dir:(Path. as_in_build_dir dir) (Path.Map. of_list_exn files)
903+ | Build_under_directory_target { directory_target_ancestor = _ } ->
904+ let + path_map = build_dir dir in
905+ let dir = Path. as_in_build_dir_exn dir in
906+ (match Targets.Produced. find_dir path_map dir with
907+ | Some files ->
908+ Filename.Map. to_list_map files ~f: (fun file digest ->
909+ Path. build (Path.Build. relative dir file), digest)
910+ |> List. filter ~f: (fun (path , _ ) -> File_selector. test g path)
911+ |> Path.Map. of_list_exn
912+ |> Dep.Fact.Files. create ~dir
913+ | None -> Dep.Fact.Files. create Path.Map. empty)
901914 ;;
902915
903916 let eval_impl g =
@@ -925,7 +938,7 @@ end = struct
925938 |> Filename.Set. of_list
926939 |> Filename_set. create ~dir
927940 |> Memo. return
928- | Build_under_directory_target _ ->
941+ | Build_under_directory_target { directory_target_ancestor = _ } ->
929942 (* To evaluate a glob in a generated directory, we have no choice but to build the
930943 whole directory, so we might as well build the predicate. *)
931944 let + facts = Pred. build g in
@@ -976,9 +989,9 @@ end = struct
976989 let build_file path = Memo. exec (Lazy. force build_file_memo) path >> | fst
977990
978991 let build_dir path =
979- let + digest , kind = Memo. exec (Lazy. force build_file_memo) path in
992+ let + (_ : Digest.t ) , kind = Memo. exec (Lazy. force build_file_memo) path in
980993 match kind with
981- | Dir_target { targets } -> digest, targets
994+ | Dir_target { targets } -> targets
982995 | File_target ->
983996 Code_error. raise " build_dir called on a file target" [ " path" , Path. to_dyn path ]
984997 ;;
@@ -1041,7 +1054,7 @@ let file_exists fn =
10411054 Memo. return
10421055 (Path.Build.Map. mem rules_here.by_file_targets (Path. as_in_build_dir_exn fn))
10431056 | Build_under_directory_target { directory_target_ancestor } ->
1044- let + _digest, path_map = build_dir (Path. build directory_target_ancestor) in
1057+ let + path_map = build_dir (Path. build directory_target_ancestor) in
10451058 Targets.Produced. mem path_map (Path. as_in_build_dir_exn fn)
10461059;;
10471060
@@ -1056,7 +1069,7 @@ let files_of ~dir =
10561069 |> Filename_set. create ~dir
10571070 |> Memo. return
10581071 | Build_under_directory_target { directory_target_ancestor } ->
1059- let + _digest, path_map = build_dir (Path. build directory_target_ancestor) in
1072+ let + path_map = build_dir (Path. build directory_target_ancestor) in
10601073 let filenames =
10611074 let dir = Path. as_in_build_dir_exn dir in
10621075 match Targets.Produced. find_dir path_map dir with
0 commit comments